perm filename CONTRL.MSS[WHT,LSP] blob
sn#754055 filedate 1984-05-12 generic text, type T, neo UTF8
@Part[Contrl, Root = "CLM.MSS"]
@Comment{Chapter of Common Lisp Manual. Copyright 1984 Guy L. Steele Jr.⎇
@MyChapter[Control Structure]
@Index[control structure]
@Index[flow of control]
@Index[environment structure]
@clisp provides a variety of special structures for organizing
programs. Some have to do with flow of control (control structures),
while others control access to variables (environment structures).
Some of these features are implemented as special forms;
other are implemented as macros, which typically expand into
complex program fragments expressed in terms of special forms
or other macros.
Function application is the primary method for construction of @xlisp
programs. Operations are written as the application of a function
to its arguments. Usually, @xlisp programs are written as a large collection
of small functions, each of which implements a simple operation.
These functions operate by calling one another, and so larger
operations are defined in terms of smaller ones.
@xlisp functions may call upon themselves recursively,
either directly or indirectly.
While the @xlisp language
is more applicative in style than statement-oriented, it
nevertheless provides many operations that produce side effects, and
consequently requires constructs for controlling the sequencing of
side effects. The construct
@Specref[progn], which is roughly equivalent to an @c[algol] @b[begin]-@b[end]
block with all its semicolons, executes a number of forms sequentially,
discarding the values of all but the last.
Many @xlisp control constructs
include sequencing implicitly, in which case they are said to
provide an ``implicit @f[progn].''
@Index{implicit @f[progn]⎇
Other sequencing constructs include @Macref[prog1] and @Macref[prog2].
For looping, @clisp provides the general iteration facility
@Macref[do] as well as a variety
of special-purpose iteration facilities for iterating or mapping
over various data structures.
@clisp provides the simple one-way conditionals @f[when] and @f[unless],
the simple two-way conditional @f[if], and the more general multi-way
conditionals such as @f[cond] and @f[case]. The choice of which form
to use in any particular situation is a matter of taste and
style.
Constructs for performing non-local exits with various scoping
disciplines are provided: @Specref[block], @Macref[return],
@Specref[return-from],
@Specref[catch], and @Specref[throw].
The multiple-value constructs provide an efficient way for a function
to return more than one value; see @Funref[values].
@Section[Constants and Variables]
Because some @xlisp data objects are used to represent programs,
one cannot always notate a constant data object in a program simply
by writing the notation for the object unadorned; it would ambiguous
whether a constant object or a program fragment was intended.
The @f[quote] special form resolves this ambiguity.
There are two spaces of variables in @clisp, in effect: ordinary
variables and function names. There are some similarities between
the two kinds, and in a few cases there are similar functions for
dealing with them, for example @f[boundp] and @f[fboundp].
However, for the most part the two kinds of variables are
used for very different purposes: one to name defined functions,
macros, and special forms, and the other to name data objects.
@Subsection[Reference]
The value of an ordinary variable
may be obtained simply by writing the name of the variable
as a form to be executed. Whether this is treated as the name
of a special variable or a lexical variable is determined
by the presence or absence of an applicable @f[special] declaration;
see chapter @ref[DECLAR].
The following functions and special forms allow reference to the
values of constants and variables in other ways.
@Defspec[Fun {quote⎇, Args {@i[object]⎇]
@f[(quote @i[x])] simply returns @i[x].
The @i[object] is not evaluated and may be any @xlisp object whatsoever.
This construct allows any @xlisp object to be written as a constant
value in a program.
For example:
@lisp
(setq a 43)
(list a (cons a 3)) @EV (43 (43 . 3))
(list (quote a) (quote (cons a 3)) @EV (a (cons a 3))
@Endlisp
Since @f[quote] forms are so frequently useful
but somewhat cumbersome to type, a standard abbreviation is defined for them:
any form @i[f] preceded by a single quote (@ @f[']@ ) character
is assumed to have @f[(quote )] wrapped around it to
make @f[(quote @i[f])].
For example:
@lisp
(setq x '(the magic quote hack))
@endlisp
is normally interpreted by @Funref[read] to mean
@lisp
(setq x (quote (the magic quote hack)))
@Endlisp
See section @ref[MACRO-CHARACTERS-SECTION].
@Enddefspec
@Defspec[Fun {function⎇, Args {@i[fn]⎇]
The value of @f[function] is always the functional interpretation
of @i[fn]; @i[fn] is interpreted as if it had appeared
in the functional position of a function invocation.
In particular,
if @i[fn] is a symbol, the functional definition associated with
that symbol is returned; see @Funref[symbol-function].
If @i[fn] is a lambda-expression, then a
``lexical closure'' is returned, that is, a function which when invoked
will execute the body of the lambda-expression in such a way as to
observe the rules of lexical scoping properly.
@index[closure]
For example:
@lisp
(defun adder (x) (function (lambda (y) (+ x y))))
@Endlisp
The result of @f[(adder 3)] is a function that will add @f[3] to its
argument:
@lisp
(setq add3 (adder 3))
(funcall add3 5) @EV 8
@endlisp
This works because @f[function] creates a closure of
the inner lambda-expression that is able to refer to the value @f[3]
of the variable @f[x] even after control has returned from the
function @f[adder].
More generally, a lexical closure in effect retains the ability to
refer to lexically visible @i[bindings], not just values.
Consider this code:
@lisp
(defun two-funs (x)
(list (function (lambda () x))
(function (lambda (y) (setq x y)))))
(setq funs (two-funs 6))
(funcall (car funs)) @EV 6
(funcall (cadr funs) 43) @EV 43
(funcall (car funs)) @EV 43
@endlisp
The function @f[two-funs] returns a list of two functions, each of which
refers to @i[the binding] of the variable @f[x] created on entry to
the function @f[two-funs] when it was called with argument @f[6].
This binding has the value @f[6] initially, but @f[setq] can alter
a binding. The lexical closure created for the first lambda-expression
does not ``snapshot'' the value @f[6] for @f[x] when the closure is created.
The second function can be used to alter the binding (to @f[43], in the
example), and this altered
value then becomes accessible to the first function.
In situations where a closure of a lambda-expression over the same set
of bindings may be produced more than once, the various resulting closures
may or may not be @f[eq], at the discretion of the implementation.
For example:
@lisp
(let ((x 5) (funs '()))
(dotimes (j 10)
(push #'(lambda (z)
(if (null z) (setq x 0) (+ x z)))
funs))
funs)
@endlisp
The result of the above expression is a list of ten closures.
Each logically requires only the binding of @f[x].
It is the same binding in each case,
so the ten closures may or may not be the same identical (@f[eq]) object.
On the other hand, the result of the expression
@lisp
(let ((funs '()))
(dotimes (j 10)
(let ((x 5))
(push (function (lambda (z)
(if (null z) (setq x 0) (+ x z))))
funs)))
funs)
@endlisp
is also a list of ten closures.
However, in this case no two of the closures may be @f[eq], because each
closure is over a distinct binding of @f[x], and these bindings can
be behaviorally distinguished because of the use of @f[setq].
The question of distinguishable behavior is important; the result of
the simpler expression
@lisp
(let ((funs '()))
(dotimes (j 10)
(let ((x 5))
(push (function (lambda (z) (+ x z)))
funs)))
funs)
@endlisp
is a list of ten closures that @i[may] be pairwise @f[eq]. Although
one might think that a different binding of @f[x] is involved for
each closure (which is indeed the case), the bindings cannot be distinguished
because their values are identical and immutable, there being no occurrence
of @f[setq] on @f[x]. A compiler would therefore be justified in
transforming the expression to
@lisp
(let ((funs '()))
(dotimes (j 10)
(push (function (lambda (z) (+ 5 z)))
funs))
funs)
@endlisp
where clearly the closures may be the same after all.
The general rule, then, is that the implementation is free to
have two distinct evaluations of the same @f[function] form
produce identical (@f[eq]) closures if it can prove that the
two conceptually distinct resulting closures must in fact be
behaviorally identical with respect to invocation.
This is merely a permitted optimization; a perfectly valid
implementation might simply cause every distinct evaluation of a @f[function]
form to produce a new closure object not @f[eq] to any other.
Frequently a compiler can deduce that a closure in fact does not
need to close over any variables bindings. For example,
in the code fragment
@lisp
(mapcar (function (lambda (x) (+ x 2))) y)
@endlisp
the function @f[(lambda (x) (+ x 2))] contains no references to any outside
entity. In this important special case, the same ``closure'' may be used
as the value for all evaluations of the @f[function] special form.
Indeed, this value need not be a closure object at all; it may
be a simple compiled function containing no environment information.
This example is simply a special case of the foregoing discussion and
is included as a hint to implementors familiar with previous methods
of implementing @xlisp. The distinction between closures and other
kinds of functions is somewhat pointless, actually, as @clisp defines
no particular representation for closures and no way to distinguish
between closures and non-closure functions. All that matters is that
the rules of lexical scoping be obeyed.
Since @f[function] forms are so frequently useful
but somewhat cumbersome to type, a standard abbreviation is defined for them:
any form @i[f] preceded by @f[#'] (@f[#] followed by an apostrophe)
is assumed to have @f[(function )] wrapped around it to make
@f[(function @i[f])]. For example,
@Lisp
(remove-if #'numberp '(1 a b 3))
@endlisp
is normally interpreted by @Funref[read] to mean
@lisp
(remove-if (function numberp) '(1 a b 3))
@Endlisp
See section @ref[SHARP-SIGN-MACRO-CHARACTER-SECTION].
@Enddefspec
@Defun[Fun {symbol-value⎇, Args {@i[symbol]⎇]
@f[symbol-value] returns the current value of the dynamic (special) variable
named by @i[symbol].
An error occurs if the symbol has no value; see @Funref[boundp]
and @Funref[makunbound].
Note that constant symbols are really variables that cannot be changed,
and so @f[symbol-value] may be used to get the value of
a named constant. In particular, @f[symbol-value] of a keyword
will return that keyword.
@f[symbol-value] cannot access the value of a lexical variable.
This function is particularly useful for implementing interpreters
for languages embedded in @xlisp.
The corresponding assignment primitive is @Funref[set];
alternatively, @f[symbol-value] may be used with @Macref[setf].
@Enddefun
@Defun[Fun {symbol-function⎇, Args {@i[symbol]⎇]
@f[symbol-function] returns the current global function definition
named by @i[symbol]. An error is signalled if the symbol has no function
definition; see @Funref[fboundp]. Note that the definition may be a
function or may be an object representing a special form or macro.
In the latter case, however, it is an error
to attempt to invoke the object as a function.
If it is desired to process macros, special forms, and functions
equally well, as when writing an interpreter,
it is best first to test the symbol with @Funref[macro-function]
and @Funref[special-form-p]
and then to invoke the functional value only if these
two tests both yield false.
This function is particularly useful for implementing interpreters
for languages embedded in @xlisp.
@f[symbol-function] cannot access the value of a lexical function name
produced by @Specref[flet] or @Specref[labels]; it can access only
the global function value.
The global function definition of a symbol may be altered
by using @Macref[setf] with @f[symbol-function].
Performing this operation causes the symbol to have @i[only] the
specified definition as its global function definition; any previous
definition, whether as a macro or as a function, is lost.
It is an error to attempt to redefine the name of a special
form (see Table @ref[SPECIAL-FORM-TABLE]).
@Enddefun
@Defun[Fun {boundp⎇, Args {@i[symbol]⎇]
@f[boundp] is true if the dynamic (special) variable named by @i[symbol]
has a value; otherwise, it returns @false.
See also @Funref[set] and @Funref[makunbound].
@Enddefun
@Defun[Fun {fboundp⎇, Args {@i[symbol]⎇]
@f[fboundp] is is true if the symbol has a global function definition.
Note that @f[fboundp] is true when the symbol names a special form or
macro. @Funref[macro-function] and @f[special-form-p] may be used to test
for these cases.
See also @Funref[symbol-function] and @Funref[fmakunbound].
@Enddefun
@Defun[Fun {special-form-p⎇, Args {@i[symbol]⎇]
The function @f[special-form-p] takes a symbol. If the symbol
globally names a special form,
then a non-@false value is returned; otherwise @false is returned.
A returned non-@nil value is typically a function
of implementation-dependent nature that can be used to
interpret (evaluate) the special form.
It is possible for @i[both] @f[special-form-p] and @Funref[macro-function]
to be true of a symbol. This is possible because an implementation is
permitted to implement any macro also as a special form for speed.
On the other hand, the macro definition must be available
for use by programs that understand only the standard special forms
listed in Table @Ref[Special-Form-Table].
@Enddefun
@Subsection[Assignment]
The following facilities allow the value of a variable (more specifically,
the value associated with the current binding of the variable) to be altered.
Such alteration is different from establishing a new binding.
Constructs for establishing new bindings of variables are described
in section @ref[VAR-BINDING-SECTION].
@Defspec[Fun {setq⎇, Args {@Mstar<@i[var] @i[form]>⎇]
The special form @f[(setq @i[var1] @i[form1] @i[var2] @i[form2] ...)] is the
``simple variable assignment statement'' of @xlisp.
First @i[form1] is evaluated
and the result is stored in the variable @i[var1], then @i[form2]
is evaluated and the result stored in @i[var2], and so forth.
The variables are represented as symbols, of course, and are interpreted
as referring to static or dynamic instances according to the usual rules.
Therefore @f[setq] may be used for assignment of both lexical
and special variables.
@f[setq] returns the last value assigned, that is, the result of the
evaluation of its last argument.
As a boundary case, the form @f[(setq)] is legal and returns @false.
There must be an even number of argument forms.
For example, in
@Lisp
(setq x (+ 3 2 1) y (cons x nil))
@Endlisp
@f[x] is set to @f[6], @f[y] is set to @f[(6)], and the @f[setq]
returns @f[(6)]. Note that the first assignment is performed before
the second form is evaluated, allowing that form to
use the new value of @f[x].
See also the description of @Macref[setf],
the @clisp ``general assignment statement'' that is capable of assigning
to variables, array elements, and other locations.
@Enddefspec
@Defmac[Fun {psetq⎇, Args {@Mstar<@i[var] @i[form]>⎇]
A @f[psetq] form is just like a @f[setq] form, except
that the assignments happen in parallel. First all of the forms
are evaluated, and then the variables are set to the resulting
values. The value of the @f[psetq] form is @false.
For example:
@lisp
(setq a 1)
(setq b 2)
(psetq a b b a)
a @EV 2
b @EV 1
@Endlisp
In this example, the values of @f[a] and @f[b] are exchanged by
using parallel assignment.
(If several variables are to be assigned in parallel in
the context of a loop, the @Macref[do] construct may be appropriate.)
See also the description of @Macref[setf],
the @clisp ``general parallel assignment statement'' that
is capable of assigning
to variables, array elements, and other locations.
@Enddefmac
@Defun[Fun {set⎇, Args {@i[symbol] @i[value]⎇]
@f[set] allows alteration of the value of a dynamic (special) variable.
@f[set] causes the dynamic variable named by @i[symbol] to take on
@i[value] as its value.
Only the value of the current dynamic binding is altered;
if there are no bindings in effect, the most global value is altered.
For example,
@Lisp
(set (if (eq a b) 'c 'd) 'foo)
@Endlisp
will either set @f[c] to @f[foo] or set @f[d] to @f[foo], depending
on the outcome of the test @f[(eq a b)].
@f[set] returns @i[value] as its result.
@i[set] cannot alter
the value of a local (lexically bound) variable.
The special form @Specref[setq]
is usually used for altering the values of variables
(lexical or dynamic) in programs.
@f[set] is particularly useful for implementing interpreters for
languages embedded in @xlisp.
See also @Specref[progv], a construct that performs binding rather
than assignment of dynamic variables.
@Enddefun
@Defun[Fun {makunbound⎇, Args {@i[symbol]⎇]
@Defun1[Fun {fmakunbound⎇, Args {@i[symbol]⎇]
@f[makunbound] causes the dynamic (special) variable named
by @i[symbol] to become unbound (have no value). @f[fmakunbound]
does the analogous thing for the global function definition named
by @i[symbol].
For example:
@lisp
(setq a 1)
a @EV 1
(makunbound 'a)
a @EV @r[causes an error]
(defun foo (x) (+ x 1))
(foo 4) @EV 5
(fmakunbound 'foo)
(foo 4) @EV @r[causes an error]
@Endlisp
Both functions return @i[symbol] as the result value.
@Enddefun
@Section[Generalized Variables]
In @xLisp, a variable can remember one piece of data,
that is, one @xlisp object.
The main operations on a variable are to recover that object, and
to alter the variable to remember a new object; these operations are
often called @i[access] and @i[update] operations. The concept of
variables named by symbols can be generalized to any storage location
that can remember one piece of data, no matter how that location is
named. Examples of such storage locations are the @i[car] and @i[cdr] of
a cons, elements of an array, and components of a structure.
For each kind of generalized variable, typically there are two functions
that implement the conceptual @i[access] and @i[update] operations.
For a variable, merely mentioning the name of the variable accesses it,
while the @Specref[setq] special form can be used to update it.
The function @Funref[car] accesses the @i[car] of a cons,
and the function @Funref[rplaca] updates it.
The function @Funref[symbol-value] accesses the dynamic value of a variable
named by a given symbol, and the function @Funref[set] updates it.
Rather than thinking about two distinct functions that respectively
access and update a storage location somehow deduced from their
arguments, we can instead simply think of a call to the access function
with given arguments as a @i[name] for the storage location. Thus, just
as @f[x] may be considered a name for a storage location (a variable), so
@f[(car x)] is a name for the @i[car] of some cons (which is in turn
named by @f[x]). Now, rather than having to remember two functions for
each kind of generalized variable (having to remember, for example, that
@f[rplaca] corresponds to @f[car]), we adopt a uniform syntax for updating
storage locations named in this way, using the @f[setf] macro.
This is analogous to the way we use the @f[setq] special form to convert
the name of a variable (which is also a form that accesses it) into a
form that updates it. The uniformity of this approach is illustrated in
the following table:
@lisp
@Tabset[+1.6 in, +1.8 in]
@r[@ux[Access function@\Update function@\Update using @f[setf]@>]]
x@\(setq x datum)@\(setf x datum)
(car x)@\(rplaca x datum)@\(setf (car x) datum)
(symbol-value x)@\(set x datum)@\(setf (symbol-value x) datum)
@Endlisp
@nopara
@f[setf] is actually a macro that examines an access form and
produces a call to the corresponding update function.
Given the existence of @f[setf] in @clisp, it is not necessary to have
@f[setq], @f[rplaca], and @f[set]; they are redundant. They
are retained in @clisp because of their historical importance in @xlisp.
However, most other update functions (such as @f[putprop], the update
function for @Funref[get]) have been eliminated from @clisp
in the expectation that @f[setf] will be uniformly used in their place.
@Defmac[Fun {setf⎇, Args {@Mstar<@i[place] @i[newvalue]>⎇]
@f[(setf @i[place] @i[newvalue])] takes a form @i[place] that when evaluated
@i[accesses] a data object in some location and ``inverts''
it to produce a corresponding form to @i[update] the location.
A call to the @f[setf] macro therefore
expands into an update form that stores the result of evaluating
the form @i[newvalue] into the place referred to by the @i[access-form].
If more than one @i[place]-@i[newvalue] pair is specified,
the pairs are processed sequentially; that is,
@Lisp
(setf @i[place1] @i[newvalue1]
@i[place2] @i[newvalue2])
...
@i[placen] @i[newvaluen])
@Endlisp
is precisely equivalent to
@lisp
(progn (setf @i[place1] @i[newvalue1])
(setf @i[place2] @i[newvalue2])
...
(setf @i[placen] @i[newvaluen]))
@Endlisp
For consistency, it is legal to write @f[(setf)], which simply returns @nil.
The form @i[place] may be any one of the following:
@Begin[Itemize]
The name of a variable (either lexical or dynamic).
@Begin[Multiple]
A function call form whose first element is the name of
any one of the following functions:
@Begin[Format]
@tabset[+1in, +1in, +1.3in]
@f[aref]@\@f[car]@\@f[svref]@\
@f[nth]@\@f[cdr]@\@f[get]@\
@f[elt]@\@f[caar]@\@f[getf]@\@f[symbol-value]
@f[rest]@\@f[cadr]@\@f[gethash]@\@f[symbol-function]
@f[first]@\@f[cdar]@\@f[documentation]@\@f[symbol-plist]
@f[second]@\@f[cddr]@\@f[fill-pointer]@\@f[macro-function]
@f[third]@\@f[caaar]@\@f[caaaar]@\@f[cdaaar]
@f[fourth]@\@f[caadr]@\@f[caaadr]@\@f[cdaadr]
@f[fifth]@\@f[cadar]@\@f[caadar]@\@f[cdadar]
@f[sixth]@\@f[caddr]@\@f[caaddr]@\@f[cdaddr]
@f[seventh]@\@f[cdaar]@\@f[cadaar]@\@f[cddaar]
@f[eighth]@\@f[cdadr]@\@f[cadadr]@\@f[cddadr]
@f[ninth]@\@f[cddar]@\@f[caddar]@\@f[cdddar]
@f[tenth]@\@f[cdddr]@\@f[cadddr]@\@f[cddddr]
@End[Format]
@End[Multiple]
A function call form whose first element is the name of
a selector function constructed by @Macref[defstruct].
@Begin[Multiple]
A function call form whose first element is the name of
any one of the following functions, provided that the new value
is of the specified type so that it can be used to
replace the specified ``location'' (which is in each of these cases
not truly a generalized variable):
@Begin[Format]
@Tabset[+2 in]
@ux[Function name@\Required type]
@f[char]@\@f[string-char]
@f[schar]@\@f[string-char]
@f[bit]@\@f[bit]
@f[sbit]@\@f[bit]
@f[subseq]@\@f[sequence]
@End[Format]
In the case of @f[subseq], the replacement value must be a sequence
whose elements may be contained by the sequence argument to @f[subseq].
(Note that this is not so stringent as to require that the
replacement value be a sequence of the same type as the sequence
of which the subsequence is specified.)
If the length of the replacement value does not equal the length of
the subsequence to be replaced, then the shorter length determines
the number of elements to be stored, as for the function @Funref[replace].
@End[Multiple]
@Begin[Multiple]
A function call form whose first element is the name of
any one of the following functions, provided that the specified argument
to that function is in turn a @i[place] form;
in this case the new @i[place] has stored back into it the
result of applying the specified ``update'' function
(which is in each of these cases not a true update function):
@Begin[Format]
@Tabset[+1.25 in, +1.7 in]
@ux[Function name@\Argument that is a @i[place]@\Update function used]
@f[char-bit]@\first@\@f[set-char-bit]
@f[ldb]@\second@\@f[dpb]
@f[mask-field]@\second@\@f[deposit-field]
@End[Format]
@End[Multiple]
@Begin[Multiple]
A @Specref[the] type declaration form, in which case the declaration is
transferred to the @i[newvalue] form, and the resulting @f[setf] form is
analyzed. For example,
@Lisp
(setf (the integer (cadr x)) (+ y 3))
@Endlisp
is processed as if it were
@Lisp
(setf (cadr x) (the integer (+ y 3)))
@Endlisp
@End[Multiple]
@Begin[Multiple]
A call to @f[apply] where the first argument form is of the form
@f[#'@i[name]], that is, @f[(function @i[name])], where @i[name]
is the name of a function, calls to which are recognized as places by @f[setf].
Suppose that the use of @f[setf] with @f[apply] looks like this:
@lisp
(setf (apply #'@i[name] @i[x1] @i[x2] ... @i[xn] @i[rest]) @i[x0])
@endlisp
The @f[setf] method for the function @i[name] must be such that
@lisp
(setf (@i[name] @i[z1] @i[z2] ... @i[zm]) @i[z0])
@endlisp
expands into a store form
@lisp
(@i[storefn] @i[zi@-[@subr[1]]] @i[zi@-[@subr[2]]] ... @i[zi@-[@subi[k]]] @i[zm])
@endlisp
That is, it must expand into a function call such that all arguments but
the last may be any permutation or subset of the new value @i[z0] and
the arguments of the access form, but the @i[last] argument of the storing
call must be the same as the last argument of the access call.
See @Macref[define-setf-method] for more details on accessing
and storing forms.
Given this, the @f[setf]-of-@f[apply] form shown above expands into
@lisp
(apply #'@i[storefn] @i[xi@-[@subr[1]]] @i[xi@-[@subr[2]]] ... @i[xi@-[@subi[k]]] @i[rest])
@endlisp
As an example, suppose that the variable @f[indexes] contains a list
of subscripts for a multidimensional array @i[foo] whose rank is not
known until run time. One may access the indicated
element of the array by writing
@lisp
(apply #'aref foo indexes)
@endlisp
and one may alter the value of the indicated element to have the value
of @f[newvalue] by writing
@lisp
(setf (apply #'aref foo indexes) newvalue)
@endlisp
@End[Multiple]
A macro call, in which case @f[setf] expands the macro call and
then analyzes the resulting form.
Any form for which a @Macref[defsetf]
or @Macref[define-setf-method] declaration has been made.
@End[Itemize]
@f[setf] carefully arranges to preserve the usual left-to-right
order in which the various subforms are evaluated.
On the other hand,
the exact expansion for any particular form is not guaranteed and
may even be implementation-dependent; all that is guaranteed is that
the expansion of a @f[setf] form will be an update form that works
for that particular implementation, and that the left-to-right evaluation
of subforms is preserved.
The ultimate result of evaluating a @f[setf] form is the value
of @i[newvalue]. Therefore @f[(setf (car x) y)] does not expand
into precisely @f[(rplaca x y)], but into something more like
@Lisp
(let ((G1 x) (G2 y)) (rplaca G1 G2) G2)
@Endlisp
the precise expansion being implementation-dependent.
The user can define new @f[setf] expansions by using @Macref[defsetf].
@Enddefmac
@Defmac[Fun {psetf⎇, Args {@Mstar<@i[place] @i[newvalue]>⎇]
@f[psetf] is like @f[setf] except that if more than one @i[place]-@i[newvalue]
pair is specified then the assignments of new values to places are
done in parallel. More precisely, all subforms that are to be evaluated
are evaluated from left to right; after all evaluations have been performed,
all of the assignments are performed in an unpredictable order.
(The unpredictability matters only if more than one @i[place] form
refers to the same place.)
@f[psetf] always returns @false.
@Enddefmac
@Defmac[Fun {shiftf⎇, Args {@Mplus<@i[place]> @i[newvalue]⎇]
Each @i[place] form may be any form acceptable
as a generalized variable to @Macref[setf].
In the form @f[(shiftf @i[place1] @i[place2] ... @i[placen] @i[newvalue])],
the values in @i[place1] through @i[placen] are accessed and saved,
and @i[newvalue] is evaluated, for a total of @i[n]+1 values in all.
Values 2 through @i[n]+1 are then stored into @i[place1] through @i[placen],
and value 1 (the original value of @i[place1]) is returned.
It is as if all the places form a shift register; the @i[newvalue]
is shifted in from the right, all values shift over to the left one place,
and the value shifted out of @i[place1] is returned. For example:
@Lisp
(setq x (list 'a 'b 'c)) @EV (a b c)
(shiftf (cadr x) 'z) @EV b
@r[and now] x @EV (a z c)
(shiftf (cadr x) (cddr x) 'q) @EV z
@r[and now] x @EV (a (c) . q)
@Endlisp
The effect of @f[(shiftf @i[place1] @i[place2] ... @i[placen] @i[newvalue])]
is roughly equivalent to
@Lisp
(let ((@i[var1] @i[place1])
(@i[var2] @i[place2])
...
(@i[varn] @i[placen]))
(setf @i[place1] @i[var2])
(setf @i[place2] @i[var3])
...
(setf @i[placen] @i[newvalue])
@i[var1])
@Endlisp
except that the latter would evaluate any subforms of each @i[place] twice,
whereas @f[shiftf] takes care to evaluate them only once.
For example:
@Lisp
(setq n 0)
(setq x '(a b c d))
(shiftf (nth (setq n (+ n 1)) x) 'z) @EV b
@r[and now] x @EV (a z c d)
@i[but]
(setq n 0)
(setq x '(a b c d))
(prog1 (nth (setq n (+ n 1)) x)
(setf (nth (setq n (+ n 1)) x) 'z)) @EV b
@r[and now] x @EV (a b z d)
@Endlisp
Moreover, for certain @i[place] forms @f[shiftf] may be
significantly more efficient than the @f[prog1] version.
@Rationale{@f[shiftf] and @f[rotatef] have been included in @clisp
as generalizations of two-argument versions formerly called @f[swapf]
and @f[exchf]. The two-argument versions have been found to be
very useful, but the names were easily confused. The generalization
to many argument forms and the change of names were both inspired
by the work of Suzuki @Cite[SUZUKI-POINTER-ROTATION],
which indicates that use of these primitives can make certain complex
pointer-manipulation programs clearer and easier to prove correct.⎇
@Enddefun
@Defmac[Fun {rotatef⎇, Args {@Mstar<@i[place]>⎇]
Each @i[place] form may be any form acceptable
as a generalized variable to @Macref[setf].
In the form @f[(rotatef @i[place1] @i[place2] ... @i[placen])],
the values in @i[place1] through @i[placen] are accessed and saved.
Values 2 through @i[n] and value 1 are then stored into @i[place1] through @i[placen].
It is as if all the places form an end-around shift register
that is rotated one place to the left, with the value of @i[place1]
being shifted around the end to @i[placen].
Note that @f[(rotatef @i[place1] @i[place2])] exchanges the contents
of @i[place] and @i[place2].
The effect of @f[(rotatef @i[place1] @i[place2] ... @i[placen] @i[newvalue])]
is roughly equivalent to
@Lisp
(psetf @i[place1] @i[place2]
@i[place2] @i[place3]
...
@i[placen] @i[place1])
@Endlisp
except that the latter would evaluate any subforms of each @i[place] twice,
whereas @f[rotatef] takes care to evaluate them only once.
Moreover, for certain @i[place] forms @f[rotatef] may be
significantly more efficient.
@f[rotatef] always returns @false.
@Enddefun
Other macros that manipulate generalized variables include
@Funref[getf], @Macref[remf],
@Macref[incf], @Macref[decf], @Macref[push], @Macref[pop],
@Macref[assert], @Macref[ctypecase], and @Macref[ccase].
Macros that manipulate generalized variables must guarantee the ``obvious''
semantics: subforms of generalized-variable references are
evaluated exactly as many times as they appear in the source program, and
they are evaluated in exactly the same order as they appear in the source
program.
In generalized-variable references such as @f[shiftf], @f[incf], @f[push],
and @f[setf] of @f[ldb], the generalized variables are both read and
written in the same reference. Preserving the source program order of
evaluation and the number of evaluations is particularly important.
As an example of these semantic rules, in the generalized-variable
reference @f[(setf @i[reference] @i[value])] the @i[value] form
must be evaluated @i[after] all the subforms of the reference because
the @i[value] form appears to the right of them.
The expansion of these macros must consist of code that follows these
rules or has the same effect as such code. This is accomplished by
introducing temporary variables bound to the subforms of the reference.
As an optimization in the implementation,
temporary variables may be eliminated whenever it
can be proven that removing them has no effect on the semantics of the program.
For example, a constant need never be saved in a temporary variable.
A variable, or any form that does not have side effects, need not be
saved in a temporary variable if it can be proven that its value will
not change within the scope of the generalized-variable reference.
@clisp provides built-in facilities to take care of
these semantic complications and optimizations. Since the required
semantics can be guaranteed by these facilities, the user does not
have to worry about writing correct code for them, especially in
complex cases. Even experts can become confused and make mistakes
while writing this sort of code.
Another reason for building in these functions is that the
appropriate optimizations will differ from implementation to
implementation. In some implementations most of the optimization is
performed by the compiler, while in others a simpler compiler is used and
most of the optimization is performed in the macros. The cost of
binding a temporary variable relative to the cost of other @xLisp
operations may differ greatly between one implementation
and another, and some implementations may find it
best never to remove temporary variables except in the simplest cases.
A good example of the issues involved can be seen in the following
generalized-variable reference:
@lisp
(incf (ldb byte-field variable))
@endlisp
This ought to expand into something like
@lisp
(setq variable
(dpb (1+ (ldb byte-field variable))
byte-field
variable))
@endlisp
In this expansion example we have
ignored the further complexity of returning the correct
value, which is the incremented byte, not the new value of @f[variable].
Note that the variable @f[byte-field] is evaluated twice, and the
variable @f[variable] is referred to three times:
once as the location in which to store a value,
and twice during the computation of that value.
Now consider this expression:
@lisp
(incf (ldb (aref byte-fields (incf i))
(aref (determine-words-array) i)))
@endlisp
It ought to expand into something like this:
@lisp
(let ((temp1 (aref byte-fields (incf i)))
(temp2 (determine-words-array)))
(setf (aref temp2 i)
(dpb (1+ (ldb temp1 (aref temp2 i)))
temp1
(aref temp2 i))))
@endlisp
Again we have ignored the complexity of returning the correct value.
What is important here is that the expressions @f[(incf i)]
and @f[(determine-words-array)]
must not be duplicated because each may have a side effect or
be affected by side effects.
The @clisp facilities provided to deal with these semantic issues include:
@begin[itemize]
Built-in macros such as @f[setf] and @f[push] that follow the semantic rules.
The @f[define-modify-macro] macro, which allows new generalized-variable
manipulating macros (of a certain restricted kind) to be defined easily.
It takes care of the semantic rules automatically.
The @f[defsetf] macro, which allows new types of generalized-variable references
to be defined easily. It takes care of the semantic rules automatically.
The @f[define-setf-method] macro and the @f[get-setf-method] function, which
provide access to the internal mechanisms when it is necessary
to define a complicated new type of generalized-variable reference
or generalized-variable-manipulating macro.
@end[itemize]
@Defmac[Fun {define-modify-macro⎇, Args {@i[name] @i[lambda-list] @i[function] @Mopt<@i[doc-string]>⎇]
This macro defines a read-modify-write macro
named @i[name]. An example of such a macro is @Macref[incf]. The first
subform of the macro will be a generalized-variable reference.
The @f[function] is literally the function to apply to the old contents of the
generalized-variable to get the new contents; it is not evaluated.
@i[lambda-list] describes
the remaining arguments for the @i[function]; these arguments come from
the remaining subforms of the macro after the generalized-variable reference.
@i[lambda-list] may contain @optional and @rest markers.
(The @key marker is not permitted here; @rest suffices for the purposes
of @f[define-modify-macro].)
@i[doc-string] is documentation for the macro @i[name] being defined.
The expansion of a @f[define-modify-macro] is equivalent to the following, except
that it generates code that follows the semantic rules outlined above.
@lisp
(defmacro @i[name] (@i[reference] . @i[lambda-list])
@i[doc-string]
@bq@;(setf ,@i[reference]
(@i[function] ,@i[reference] ,@i[arg1] ,@i[arg2] ...)))
@endlisp
where @i[arg1], @i[arg2], ..., are the parameters appearing in @i[lambda-list];
appropriate provision is made for a @rest parameter.
As an example, @Macref[incf] could have been defined by:
@lisp
(define-modify-macro incf (&optional (delta 1)) +)
@endlisp
An example of a possibly useful macro not predefined in @clisp is:
@lisp
(define-modify-macro unionf (other-set &rest keywords) union)
@endlisp
@enddefmac
@Defmac[Fun {defsetf⎇, Args {@i[access-fn] @Mgroup'@!@i[update-fn] @Mopt<@i[doc-string]> @Mor
@/@i[lambda-list] (@i[store-variable]) @Mstar<@i[declaration] @mor @i[doc-string]> @Mstar<@i[form]>'⎇]
This defines how to @f[setf] a generalized-variable reference
of the form @f[(@i[access-fn] ...)]. The value of a generalized-variable
reference can always be obtained simply by evaluating it, so @i[access-fn]
should be the name of a function or a macro.
The user of @f[defsetf] provides a description of how to store into the
generalized-variable reference and return the value that was stored (because
@f[setf] is defined to return this value). The implementation
of @f[defsetf] takes care of
ensuring that subforms of the reference are evaluated exactly once and
in the proper left-to-right order. In order to do this,
@f[defsetf] requires that @i[access-fn] be a function or a macro
that evaluates its arguments, behaving like a function.
Furthermore, a @f[setf] of a call on @i[access-fn] will also evaluate
all of @i[access-fn]'s arguments; it cannot treat any of them specially.
This means that @f[defsetf] cannot be used to describe how to store into
a generalized variable that is a byte, such as @f[(ldb field reference)].
To handle situations that do not fit the restrictions imposed by @f[defsetf],
use @Macref[define-setf-method], which gives the user additional control
at the cost of increased complexity.
A @f[defsetf] declaration may take one of two forms.
The simple form of @f[defsetf] is
@Lisp
(defsetf @i[access-fn] @i[update-fn] @Mopt<@i[doc-string]>)
@Endlisp
The @i[update-fn] must name a function (or macro) that takes one more argument
than @i[access-fn] takes. When @f[setf] is given a @i[place]
that is a call on @i[access-fn], it expands into
a call on @i[update-fn] that is given all the arguments to
@i[access-fn] and also, as its last argument, the new value
(which must be returned by @i[update-fn] as its value).
For example, the effect of
@lisp
(defsetf symbol-value set)
@Endlisp
is built into the @clisp system.
This causes the form @f[(setf (symbol-value foo) fu)]
to expand into @f[(set foo fu)].
Note that
@lisp
(defsetf car rplaca)
@endlisp
would be incorrect because @Funref[rplaca] does not return its last argument.
The complex form of @f[defsetf] looks like
@lisp
(defsetf @i[access-fn] @i[lambda-list] (@i[store-variable]) . @i[body])
@endlisp
and resembles @Macref[defmacro]. The @i[body] must
compute the expansion of a @f[setf] of a call on @i[access-fn].
@i[lambda-list] describes the arguments of @i[access-fn]. @optional,
@rest, and @key markers are permitted in @i[lambda-list].
Optional arguments may
have defaults and ``supplied-p'' flags. The @i[store-variable] describes the
value to be stored into the generalized-variable reference.
@Rationale{The @i[store-variable] is enclosed
in parentheses to provide for an extension
to multiple store variables that would
receive multiple values from the second subform of @f[setf].
The rules given below for coding @f[setf] methods discuss
the proper handling of multiple store variables to allow for
the possibility that this extension may be incorporated into @clisp
in the future.⎇
The @i[body] forms can be written as if the variables in the @i[lambda-list]
were bound to subforms of the call on @i[access-fn] and the
@i[store-variable] were bound to the second subform of @f[setf].
However, this is not actually the case. During the evaluation of the
@i[body] forms, these variables are bound to names of temporary variables,
generated as if by @Funref[gensym] or @Funref[gentemp],
that will be bound by the
expansion of @f[setf] to the values of those subforms. This binding
permits the
@i[body] forms to be written without regard for order-of-evaluation
issues. @f[defsetf] arranges for the temporary variables to be
optimized out of the final result in cases where that is possible. In
other words, an attempt is made by @f[defsetf] to generate
the best code possible in a particular implementation.
Note that the code generated by the @i[body] forms must include provision
for returning the correct value (the value of @i[store-variable]). This is
handled by the @i[body] forms rather than by @f[defsetf] because
in many cases this value can be returned at no extra cost, by calling a
function that simultaneously stores into the generalized variable and
returns the correct value.
An example of the use of the complex form of @f[defsetf]:
@lisp
(defsetf subseq (sequence start &optional end) (new-sequence)
@bq@;(progn (replace ,sequence ,new-sequence
:start1 ,start :end1 ,end)
,new-sequence))
@endlisp
@Enddefmac
The underlying theory by which @f[setf] and related macros arrange to
conform to the semantic rules given above is that from any
generalized-variable reference one may derive its ``@f[setf] method,''
which describes how to store into that reference and which subforms of
it are evaluated.
@Incompatibility{To avoid confusion,
it should be noted that the use of the word ``method'' here in connection
with @f[setf] has nothing to do with its use in @lmlisp in connection
with message-passing and the @lmlisp ``flavor system.''⎇
Given knowledge of the subforms of the reference,
it is possible to avoid evaluating them multiple times or in the wrong
order. A @f[setf] method for a given access form can be expressed as
five values:
@begin[itemize]
A list of @i[temporary variables].
A list of @i[value forms] (subforms of the given form)
to whose values the temporary variables are to be bound.
A second list of temporary variables, called @i[store variables].
A @i[storing form].
An @i[accessing form].
@end[itemize]
The temporary variables will be bound to the values of
the value forms as if by @Specref[let*]; that is, the
value forms will be evaluated in the order given
and may refer to the values of earlier value forms
by using the corresponding variables.
The store variables are to be bound to the values of the @i[newvalue] form,
that is, the values to be
stored into the generalized variable. In almost all cases only a
single value is to be stored, and there is only one store variable.
The storing form and the accessing form may contain references to the
the temporary variables (and also, in the case of the storing form,
to the store variables). The accessing form returns the value of the
generalized variable. The storing form modifies the value of the
generalized variable and guarantees to return the values of the
store variables as
its values; these are the correct values for @f[setf] to
return. (Again, in most cases there is a single store variable
and thus a single value to be returned.)
The value returned by the accessing form is, of course,
affected by execution of the storing form, but either of these
forms may be evaluated any number of times, and therefore should be
free of side effects (other than the storing action of the storing form).
The temporary variables and the store variables are generated names,
as if by @Funref[gensym] or @Funref[gentemp],
so that there is never any problem of name clashes among them, or
between them and other variables in the program. This is necessary to
make the special forms that do more than one @f[setf] in parallel work
properly; these are @f[psetf], @f[shiftf], and @f[rotatef]. Computation
of the @f[setf] method must always create new variable names; it may not return
the same ones every time.
Some examples of @f[setf] methods for particular forms:
@begin[itemize]
@Begin[Multiple]
For a variable @f[x]:
@lisp
()
()
(g0001)
(setq x g0001)
x
@endlisp
@End[Multiple]
@Begin[Multiple]
For @f[(car @i[exp])]:
@lisp
(g0002)
(@i[exp])
(g0003)
(progn (rplaca g0002 g0003) g0003)
(car g0002)
@endlisp
@End[Multiple]
@Begin[Multiple]
For @f[(subseq @i[seq] @i[s] @i[e])]:
@lisp
(g0004 g0005 g0006)
(@i[seq] @i[s] @i[e])
(g0007)
(progn (replace g0004 g0007 :start1 g0005 :end1 g0006)
g0007)
(subseq g0004 g0005 g0006)
@endlisp
@End[Multiple]
@end[itemize]
@Defmac[Fun {define-setf-method⎇, Args {@i[access-fn] @i[lambda-list] @Mstar<@i[declaration] @mor @i[doc-string]> @Mstar<@i[form]>⎇]
This defines how
to @f[setf] a generalized-variable reference that is of the form
@f[(@i[access-fn]...)]. The value of a generalized-variable reference can
always be obtained simply by evaluating it, so @i[access-fn] should be the
name of a function or a macro.
The @i[lambda-list] describes the subforms of the generalized-variable
reference, as with @Macref[defmacro]. The result of evaluating the
@i[forms] in the body must be five values representing
the @f[setf] method, as described
above. Note that @f[define-setf-method] differs from the complex form of
@f[defsetf] in that while the body is being executed the variables in
@i[lambda-list] are bound to parts of the generalized-variable reference,
not to temporary variables that will be bound to the values of such parts.
In addition, @f[define-setf-method] does not have @f[defsetf]'s
restriction that @i[access-fn] must be a function or a function-like
macro; an arbitrary @f[defmacro] destructuring pattern is permitted in
@i[lambda-list].
By definition there are no good small examples of @f[define-setf-method]
because the easy cases can all be handled by @f[defsetf].
A typical use is to define the @f[setf] method for @Funref[ldb]:
@lisp
;;; SETF method for the form (LDB bytespec int).
;;; Recall that the int form must itself be suitable for SETF.
(define-setf-method ldb (bytespec int)
(multiple-value-bind (temps vals stores
store-form access-form)
(get-setf-method int) ;Get SETF method for int.
(let ((btemp (gensym)) ;Temp var for byte specifier.
(store (gensym)) ;Temp var for byte to store.
(stemp (first stores))) ;Temp var for int to store.
;; Return the SETF method for LDB as five values.
(values (cons btemp temps) ;Temporary variables.
(cons bytespec vals) ;Value forms.
(list store) ;Store variables.
@bq@;(let ((,stemp (dpb ,store ,btemp ,access-form)))
,store-form
,store) ;Storing form.
@bq@;(ldb ,btemp ,access-form) ;Accessing form.
))))
@endlisp
@enddefmac
@Defun[Fun {get-setf-method⎇, Args {@i[form]⎇]
@f[get-setf-method] returns
five values constituting the @f[setf] method for @i[form].
The @i[form] must be a
generalized-variable reference. @f[get-setf-method] takes care of
error-checking and macro expansion and guarantees to return exactly one
store-variable.
As an example, an extremely simplified version of @f[setf],
allowing no more and no fewer than two
subforms, containing no optimization to remove unnecessary variables, and
not allowing storing of multiple values, could be defined by:
@lisp
(defmacro setf (reference value)
(multiple-value-bind (vars vals stores store-form access-form)
(get-setf-method reference)
(declare (ignore access-form))
@bq@;(let* ,(mapcar #'list
(append vars stores)
(append vals (list value)))
,store-form)))
@endlisp
@EndDefun
@Defun[Fun {get-setf-method-multiple-value⎇, Args {@i[form]⎇]
@f[get-setf-method-multiple-value]
returns five values constituting the @f[setf] method for @i[form].
The @i[form] must be a
generalized-variable reference. This is the same as @f[get-setf-method]
except that it does not check the number of store-variables; use this
in cases that allow storing multiple values into a generalized variable.
There are no such cases in standard @clisp, but this function is provided
to allow for possible extensions.
@EndDefun
@Section[Function Invocation]
The most primitive form for function invocation in @xlisp of course
has no name; any list that has no other interpretation
as a macro call or special form is taken to be a function call.
Other constructs are provided for less common but
nevertheless frequently useful situations.
@Defun[Fun{apply⎇, Args {@i[function] @i[arg] @rest @i[more-args]⎇]
This applies @i[function] to a list of arguments.
@i[function] may be a
compiled-code object, or a lambda-expression, or a symbol; in the latter
case the global functional value of that symbol is used (but it is
illegal for the symbol to be the name of a macro or special form).
The arguments for the @i[function] consist of the last argument
to @f[apply] appended to the end of a list of all the other
arguments to @f[apply] but the @i[function] itself;
it is as if all the arguments to @f[apply] except the @i[function]
were given to @Funref[list*] to create the argument list.
For example:
@lisp
(setq f '+) (apply f '(1 2)) @EV 3
(setq f #'-) (apply f '(1 2)) @EV -1
(apply #'max 3 5 '(2 7 3)) @EV 7
(apply 'cons '((+ 2 3) 4)) @EV
((+ 2 3) . 4) @i[not] (5 . 4)
(apply #'+ '()) @EV 0
@Endlisp
Note that if the function takes keyword arguments, the
keywords as well as the corresponding values must appear in the argument
list:
@Lisp
(apply #'(lambda (@key a b) (list a b)) '(:b 3)) @EV (@nil 3)
@Endlisp
This can be very useful in conjunction with the @allowotherkeys feature:
@lisp
(defun foo (size @rest keys @key double @allowotherkeys)
(let ((v (apply #'make-array size :allow-other-keys t keys)))
(if double (concatenate (type-of v) v v) v)))
(foo 4 :initial-contents '(a b c d) :double t)
@Ev #(a b c d a b c d)
@endlisp
@Enddefun
@Defun[Fun{funcall⎇, Args {@i[fn] @rest @i[arguments]⎇]
@f[(funcall @i[fn] @i[a1] @i[a2] ... @i[an])]
applies the function @i[fn] to the arguments
@i[a1], @i[a2], ..., @i[an].
@i[fn] may not
be a special form nor a macro; this would not be meaningful.
For example:
@lisp
(cons 1 2) @EV (1 . 2)
(setq cons (symbol-function '+))
(funcall cons 1 2) @EV 3
@Endlisp
The difference between @f[funcall] and an ordinary function call is that
the function is obtained by ordinary @xlisp evaluation rather than
by the special interpretation of the function position that normally
occurs.
@Incompatibility{The @clisp function @f[funcall] corresponds roughly to
the @interlisp primitive @f[apply*].⎇
@Enddefun
@Defcon[Var {call-arguments-limit⎇]
The value of @f[call-arguments-limit] is a positive integer that is
the upper exclusive bound on the number of arguments that may
be passed to a function. This bound depends on the implementation,
but will not be smaller than 50.
(Implementors are encouraged to make this limit as large as practicable
without sacrificing performance.)
The value of @f[call-arguments-limit] must be as
least as great as that of @conref[lambda-parameters-limit].
See also @conref[multiple-values-limit].
@Enddefcon
@Section[Simple Sequencing]
Each of the constructs in this section simply evaluates all the
argument forms in order. They differ only in what results
are returned.
@Defspec[Fun {progn⎇, Args {@Mstar<@i[form]>⎇]
The @f[progn] construct takes a number of forms and evaluates
them sequentially, in order, from left to right. The values of all
the forms but the last are discarded; whatever the last form returns
is returned by the @f[progn] form.
One says that all the forms but the last are evaluated for @i[effect],
because their execution is useful only for the side effects caused,
but the last form is executed for @i[value].
@f[progn] is the primitive control structure construct for ``compound
statements,'' such as @b[begin]-@b[end] blocks in
@c[algol]-like languages.
Many @xlisp constructs are ``implicit @f[progn]'' forms, in that
as part of their syntax each allows many forms to be written
that are to be evaluated sequentially, discarding the results
of all forms but the last and returning the results of the last form.
If the last form of the @f[progn] returns multiple values, then those
multiple values are returned by the @f[progn] form. If there are no forms
for the @f[progn], then the result is @false. These rules generally hold for
implicit @f[progn] forms as well.
@Enddefspec
@Defmac[Fun {prog1⎇, Args {@i[first] @Mstar<@i[form]>⎇]
@f[prog1] is similar to @f[progn], but it returns the value of
its @i[first] form. All the argument forms are executed sequentially;
the value the first form produces is saved while all the others are executed
and is then returned.
@f[prog1] is most commonly used to evaluate an expression with side
effects and return a value that must be computed @i[before] the side
effects happen.
For example:
@lisp
(prog1 (car x) (rplaca x 'foo))
@Endlisp
alters the @i[car] of @f[x] to be @f[foo] and returns the old @i[car]
of @f[x].
@f[prog1] always returns a single value, even if the first form
tries to return multiple values.
As a consequence of this,
@f[(prog1 @i[x])] and @f[(progn @i[x])] may behave differently
if @i[x] can produce multiple values. See @Specref[multiple-value-prog1].
A point of style:
although @f[prog1] can be used to force exactly a single value to
be returned, it is conventional to use the
function @Funref[values] for this purpose.
@Enddefmac
@Defmac[Fun {prog2⎇, Args {@i[first] @i[second] @Mstar<@i[form]>⎇]
@f[prog2] is similar to @f[prog1], but it returns the value of
its @i[second] form. All the argument forms are executed sequentially;
the value of the second form
is saved while all the other forms are executed and is then returned.
@f[prog2] is provided mostly for historical compatibility.
@Lisp
(prog2 @i[a] @i[b] @i[c] ... @i[z]) @EQ (progn @i[a] (prog1 @i[b] @i[c] ... @i[z]))
@Endlisp
Occasionally it is desirable to perform one side effect, then a value-producing
operation, then another side effect. In such a peculiar case, @f[prog2]
is fairly perspicuous.
For example:
@lisp
(prog2 (open-a-file) (process-the-file) (close-the-file))
;@r[value is that of @f[process-the-file]]
@Endlisp
@f[prog2], like @f[prog1],
always returns a single value, even if the second form
tries to return multiple values. As a consequence of this,
@f[(prog2 @i[x] @i[y])] and @f[(progn @i[x] @i[y])] may behave differently
if @i[y] can produce multiple values.
@Enddefmac
@Section[Establishing New Variable Bindings]
@label[VAR-BINDING-SECTION]
During the invocation of
a function represented by a lambda-expression (or a closure of
a lambda-expression, as produced by @f[function]),
new bindings are established for the variables that are the
paremeters of the lambda-expression. These bindings initially
have values determined by the parameter-binding protocol discussed
in section @ref[LAMBDA-EXPRESSIONS-SECTION].
The following constructs may also be used to establish bindings of variables,
both ordinary and functional.
@Defspec[Fun {let⎇, Args {(@Mstar<@i[var] @mor (@i[var] @i[value])>) @Mstar<@i[declaration]> @Mstar<@i[form]>⎇]
A @f[let] form can be used to execute a series of forms
with specified variables bound to specified values.
More precisely, the form
@Lisp
(let ((@i[var1] @i[value1])
(@i[var2] @i[value2])
...
(@i[varm] @i[valuem]))
@i[declaration1]
@i[declaration2]
...
@i[declarationp]
@i[body1]
@i[body2]
...
@i[bodyn])
@Endlisp
first evaluates the expressions @i[value1], @i[value2], and so on,
in that order, saving the resulting values.
Then all of the variables @i[varj] are bound to the corresponding
values in parallel; each binding will be a lexical binding unless
there is a @f[special] declaration to the contrary.
The expressions @i[bodyk] are then evaluated
in order; the values of all but the last are discarded
(that is, the body of a @f[let] form is an implicit @f[progn]).
The @f[let] form returns what evaluating @i[bodyn] produces (if the
body is empty, which is fairly useless, @f[let] returns @false as its value).
The bindings of the variables have lexical scope and indefinite extent.
Instead of a list @f[(@i[varj] @i[valuej])], one may write simply
@i[varj]. In this case @i[varj] is initialized to @false. As a matter
of style, it is recommended that @i[varj] be written only when that
variable will be stored into (such as by @Specref[setq]) before its first
use. If it is important that the initial value is @false rather than
some undefined value, then it is clearer to write out
@f[(@i[varj] @false)] if the initial value is intended to mean ``false'' or
@f[(@i[varj] '@empty)] if the initial value is intended to be an empty
list. Note that the code
@lisp
(let (x)
(declare (integer x))
(setq x (gcd y z))
...)
@endlisp
is incorrect; although @f[x] is indeed set before it is used,
and is set to a value of the declared type @f[integer], nevertheless
@f[x] momentarily takes on the value @nil in violation of the type
declaration.
Declarations may appear at the beginning of the body of a @f[let].
See @Specref[declare].
@Enddefspec
@Defspec[Fun {let*⎇, Args {(@Mstar<@i[var] @mor (@i[var] @i[value])>) @Mstar<@i[declaration]> @Mstar<@i[form]>⎇]
@f[let*] is similar to @Specref[let], but the bindings of variables
are performed sequentially rather than in parallel. This allows
the expression for the value of a variable to refer to variables
previously bound in the @f[let*] form.
More precisely, the form
@Lisp
(let* ((@i[var1] @i[value1])
(@i[var2] @i[value2])
...
(@i[varm] @i[valuem]))
@i[declaration1]
@i[declaration2]
...
@i[declarationp]
@i[body1]
@i[body2]
...
@i[bodyn])
@Endlisp
first evaluates the expression @i[value1], then binds the variable
@i[var1] to that value; then it evaluates @i[value2] and binds @i[var2];
and so on.
The expressions @i[bodyj] are then evaluated
in order; the values of all but the last are discarded
(that is, the body of a @f[let*] form is an implicit @f[progn]).
The @f[let*] form returns the results of evaluating @i[bodyn] (if the
body is empty, which is fairly useless, @f[let*] returns @false as its value).
The bindings of the variables have lexical scope and indefinite extent.
Instead of a list @f[(@i[varj] @i[valuej])], one may write simply @i[varj].
In this case @i[varj] is initialized to @false. As a matter of style,
it is recommended that @i[varj] be written only when that variable
will be stored into (such as by @Specref[setq]) before its first use.
If it is important that the initial value is @nil rather than
some undefined value, then it is clearer to write out
@f[(@i[varj]@ @false)] if the initial value is intended to mean ``false'' or
@f[(@i[varj]@ '@empty)] if the initial value is intended to be an empty
list.
Declarations may appear at the beginning of the body of a @f[let*].
See @Specref[declare].
@Enddefspec
@Defspec[Fun {compiler-let⎇, Args {(@Mstar<@i[var] @mor (@i[var] @i[value])>) @Mstar<@i[form]>⎇]
When executed by the @xlisp interpreter, @f[compiler-let] behaves
exactly like @Specref[let] with all the variable bindings implicitly
declared @f[special]. When the compiler processes this form,
however, no code is compiled for the bindings;
instead, the processing of the body by the compiler
(including, in particular, the expansion of any macro calls
within the body) is done with
the special variables bound to the indicated values @i[in the
execution context of the compiler]. This is primarily useful for
communication among complicated macros.
Declarations may @i[not] appear at the beginning of the body
of a @f[compiler-let].
@Rationale{Because of the unorthodox
handling by @f[compiler-let] of its variable bindings,
it would be complicated and confusing to permit declarations
that apparently referred to the variables bound by @f[compiler-let].
Disallowing declarations eliminates the problem.⎇
@enddefspec
@Defspec[Fun {progv⎇, Args {@i[symbols] @i[values] @Mstar<@i[form]>⎇]
@f[progv] is a special form that allows binding one or more dynamic
variables whose names may be determined at run time. The sequence of
forms (an implicit @f[progn])
is evaluated with the dynamic variables whose names are in the list
@i[symbols] bound to corresponding values from the list @i[values].
(If too few values are supplied, the remaining symbols are bound and then
made to have no value; see @Funref[makunbound]. If too many values are
supplied, the excess values are ignored.) The results of the @f[progv]
form are those of the last
@i[form]. The bindings of the dynamic variables are undone on
exit from the @f[progv] form. The lists of symbols and values are
computed quantities; this is what makes @f[progv] different from, for
example, @Specref[let], where the variable names are stated explicitly in
the program text.
@f[progv] is particularly useful for writing interpreters for languages
embedded in @xlisp; it provides a handle on the mechanism for binding
dynamic variables.
@Enddefspec
@Defspec[Fun {flet⎇, Args {(@Mstar"(@i[name] @i[lambda-list] @Mstar<@i[declaration] @mor @i[doc-string]> @Mstar<@i[form]>)") @Mstar<@i[form]>⎇]
@Defspec1[Fun {labels⎇, Args {(@Mstar"(@i[name] @i[lambda-list] @Mstar<@i[declaration] @mor @i[doc-string]> @Mstar<@i[form]>)") @Mstar<@i[form]>⎇]
@Defspec1[Fun {macrolet⎇, Args {(@Mstar"(@i[name] @i[varlist] @Mstar<@i[declaration] @mor @i[doc-string]> @Mstar<@i[form]>)") @Mstar<@i[form]>⎇]
@f[flet] may be used to define locally named functions. Within the
body of the @f[flet] form, function names matching those defined
by the @f[flet] refer to the locally defined functions rather than to
the global function definitions of the same name.
Any number of functions may be simultaneously defined. Each definition
is similar in format to a @Macref[defun] form: first a name,
then a parameter list (which may contain @optional, @rest, or @key
parameters), then optional declarations and documentation string,
and finally a body.
@lisp
(flet ((safesqrt (x) (sqrt (abs x))))
;; The safesqrt function is used in two places.
(safesqrt (apply #'+ (map 'list #'safesqrt longlist))))
@endlisp
The @f[labels] construct is identical in form to the @f[flet] construct.
These constructs differ
in that the scope of the defined function names for @f[flet]
encompasses only the body, whereas for @f[labels] it encompasses the
function definitions themselves. That is, @f[labels] can be used to
define mutually recursive functions, but @f[flet] cannot. This
distinction is useful. Using @f[flet] one can locally redefine a global
function name, and the new definition can refer to the global definition;
the same construction using @f[labels] would not have that effect.
@Lisp
(defun integer-power (n k) ;A highly "bummed" integer
(declare (integer n)) ; exponentiation routine.
(declare (type (integer 0 *) k))
(labels ((expt0 (x k a)
(declare (integer x a) (type (integer 0 *) k))
(cond ((zerop k) a)
((evenp k) (expt1 (* x x) (floor k 2) a))
(t (expt0 (* x x) (floor k 2) (* x a)))))
(expt1 (x k a)
(declare (integer x a) (type (integer 0 *) k))
(cond ((evenp k) (expt1 (* x x) (floor k 2) a))
(t (expt0 (* x x) (floor k 2) (* x a))))))
(expt0 n k 1)))
@Endlisp
@f[macrolet] is similar in form to @f[flet] but defines local macros,
using the same format used by @Macref[defmacro].
The names established by @f[macrolet] as names for macros are
lexically scoped.
Macros often must be expanded at ``compile time'' (more generally,
at a time before the program itself is executed), and so
the run-time values of variables are not available to macros
defined by @f[macrolet]. The precise rule is that the macro-expansion
functions defined by @f[macrolet] are defined in the @i[global] environment;
lexically scoped entities that would ordinarily be lexically apparent
are not visible within the expansion functions. However,
lexically scoped entities @i[are] visible
within the body of the @f[macrolet] form and @i[are] visible
to the code that is the expansion of a macro call. The following example
should make this clear:
@lisp
(defun foo (x flag)
(macrolet ((fudge (z)
;@r[The parameters @f[x] and @f[flag] are not accessible]
; @r[at this point; a reference to @f[flag] would be to]
; @r[the global variable of that name.]
@bq@;(if flag (* ,z ,z) ,z)))
;@r[The parameters @f[x] and @f[flag] are accessible here.]
(+ x
(fudge x)
(fudge (+ x 1)))))
@endlisp
The body of the @f[macrolet] becomes
@lisp
(+ x
(if flag (* x x) x))
(if flag (* (+ x 1) (+ x 1)) (+ x 1)))
@endlisp
after macro expansion. The occurrences of @f[x] and @f[flag] legitimately
refer to the parameters of the function @f[foo] because those parameters are
visible at the site of the macro call which produced the expansion.
@Enddefspec
@Section[Conditionals]
The traditional conditional construct in @xlisp in @f[cond].
However, @f[if] is much simpler and is directly comparable
to conditional constructs in other programming languages,
so it is considered to be primitive in @clisp and is described first.
@clisp also provides the dispatching constructs @f[case] and @f[typecase],
which are often more convenient than @f[cond].
@Defspec[Fun {if⎇, Args {@i[test] @i[then] @Mopt<@i[else]>⎇]
The @f[if] special form corresponds to the @b[if]-@b[then]-@b[else] construct
found in most algebraic programming languages.
First the form @i[test] is evaluated. If the result is not @false,
then the form @i[then] is selected; otherwise the form @i[else] is selected.
Whichever form is selected is then evaluated, and @f[if] returns
whatever evaluation of the selected form returns.
@Lisp
(if @i[test] @i[then] @i[else]) @EQ (cond (@i[test] @i[then]) (@true @i[else]))
@Endlisp
but @f[if] is considered more readable in some situations.
The @i[else] form may be omitted, in which case if the value of @i[test]
is @false then nothing is done and the value of the @f[if] form is @false.
If the value of
the @f[if] form is important in this situation, then the @Macref[and]
construct may be stylistically preferable,
depending on the context.
If the value is not important, but only the effect, then the @Macref[when]
construct may be stylistically preferable.
@Enddefspec
@Defmac[Fun {when⎇, Args {@i[test] @Mstar<@i[form]>⎇]
@f[(when @i[test] @i[form1] @i[form2] ... )]
first evaluates @i[test]. If the result is @false,
then no @i[form] is evaluated, and @false is returned.
Otherwise the @i[form]s constitute an implicit @f[progn]
and are evaluated sequentially from left to right,
and the value of the last one is returned.
@Lisp
(when @i[p] @i[a] @i[b] @i[c]) @EQ (and @i[p] (progn @i[a] @i[b] @i[c]))
(when @i[p] @i[a] @i[b] @i[c]) @EQ (cond (@i[p] @i[a] @i[b] @i[c]))
(when @i[p] @i[a] @i[b] @i[c]) @EQ (if @i[p] (progn @i[a] @i[b] @i[c]) @false)
(when @i[p] @i[a] @i[b] @i[c]) @EQ (unless (not @i[p]) @i[a] @i[b] @i[c])
@Endlisp
As a matter of style,
@f[when] is normally used to conditionally produce some side effects,
and the value of the @f[when]-form is normally not used.
If the value is relevant, then it may be
stylistically more appropriate to use @Macref[and] or @Specref[if].
@Enddefmac
@Defmac[Fun {unless⎇, Args {@i[test] @Mstar<@i[form]>⎇]
@f[(unless @i[test] @i[form1] @i[form2] ... )]
first evaluates @i[test]. If the result is @i[not] @false,
then the @i[form]s are not evaluated, and @false is returned.
Otherwise the @i[form]s constitute an implicit @f[progn]
and are evaluated sequentially from left to right,
and the value of the last one is returned.
@Lisp
(unless @i[p] @i[a] @i[b] @i[c]) @EQ (cond ((not @i[p]) @i[a] @i[b] @i[c]))
(unless @i[p] @i[a] @i[b] @i[c]) @EQ (if @i[p] @false (progn @i[a] @i[b] @i[c]))
(unless @i[p] @i[a] @i[b] @i[c]) @EQ (when (not @i[p]) @i[a] @i[b] @i[c])
@Endlisp
As a matter of style,
@f[unless] is normally used to conditionally produce some side effects,
and the value of the @f[unless]-form is normally not used.
If the value is relevant, then it may be
stylistically more appropriate to use @specref[if].
@Enddefmac
@Defmac[Fun {cond⎇, Args {@Mstar<(@i[test] @Mstar'@i[form]')>⎇]
A @f[cond] form has a number (possibly zero) of
@i[clauses], which are lists of forms.
Each clause consists of a @i[test] followed
by zero or more @i[consequents].
For example:
@lisp
(cond (@i[test-1] @i[consequent-1-1] @i[consequent-1-2] ...)
(@i[test-2])
(@i[test-3] @i[consequent-3-1] ...)
... )
@Endlisp
The first clause whose @i[test] evaluates to non-@false
is selected; all other clauses are ignored, and the consequents
of the selected clause are evaluated in order (as an implicit @f[progn]).
More specifically, @f[cond] processes its clauses in order from left to
right. For each clause, the @i[test] is evaluated. If the result is
@false, @f[cond] advances to the next clause. Otherwise, the @i[cdr] of
the clause is treated as a list of forms, or consequents; these forms are
evaluated in order from left to right, as an implicit @f[progn].
After evaluating the consequents,
@f[cond] returns without inspecting any remaining clauses.
The @f[cond] special form returns the results
of evaluating the last of the selected consequents;
if there were no consequents in
the selected clause,
then the single (and necessarily non-null) value of the @i[test] is returned.
If @f[cond] runs out of clauses (every test produced @false,
and therefore no clause was selected), the value of the @f[cond] form is
@false.
If it is desired to select the last clause unconditionally if all others
fail, the standard convention is to use @true for the @i[test].
As a matter of style, it is desirable to write a last clause
@f[(@true @false)] if the value of the @i[cond] form is to be used
for something. Similarly, it is in questionable
taste to let the last clause of
a @f[cond] be a ``singleton clause''; an explicit @true should be provided.
(Note moreover that @f[(cond ... (@i[x]))] may behave differently from
@f[(cond ... (@true @i[x]))] if @i[x] might produce multiple values;
the former always returns a single value, whereas the latter returns whatever
values @i[x] returns. However, as a matter of style it is preferable
to obtain this behavior by writing @f[(cond ... (t (values @i[x])))],
using the @Funref[values] function explicitly to indicate the discarding
of any excess values.)
For example:
@lisp
@Tabclear
@Tabset[42]
(setq z (cond (a 'foo) (b 'bar)))@\;@r[Possibly confusing]
(setq z (cond (a 'foo) (b 'bar) (@true @false)))@\;@r[Better]
(cond (a b) (c d) (e))@\;@r[Possibly confusing]
(cond (a b) (c d) (@true e))@\;@r[Better]
(cond (a b) (c d) (@true (values e)))@\;@r[Better (if one value needed)]
(cond (a b) (c))@\;@r[Possibly confusing]
(cond (a b) (t c))@\;@r[Better]
(if a b c)@\;@r[Also better]
@Endlisp
A @xlisp @f[cond] form may be compared to a continued @b[if]@b[then]-@b[else]
as found in many algebraic programming languages:
@Lisp
@Tabdivide[3]
(cond (@i[p] ...)@\@\@b[if] @i[p] @b[then] ...
(@i[q] ...)@\@=@r[roughly]@\@b[else] @b[if] @i[q] @b[then] ...
(@i[r] ...)@\@=@r[corresponds]@\@b[else] @b[if] @i[r] @b[then] ...
...@\@=@r[to]@\...
(@true ...))@\@\@b[else] ...
@Endlisp
@Enddefmac
@Defmac[Fun {case⎇, Args {@i[keyform] @Mstar<(@Mgroup"(@Mstar'@i[key]') @Mor @i[key]" @Mstar'@i[form]')>⎇]
@f[case] is a conditional that chooses one of its clauses to execute
by comparing a value to various constants, which are
typically keyword symbols, integers, or characters
(but may be any objects). Its form is as follows:
@Lisp
(case @i[keyform]
(@i[keylist-1] @i[consequent-1-1] @i[consequent-1-2] ...)
(@i[keylist-2] @i[consequent-2-1] ...)
(@i[keylist-3] @i[consequent-3-1] ...)
...)
@Endlisp
Structurally @f[case] is much like @Macref[cond],
and it behaves like @f[cond]
in selecting one clause and then executing all consequents of that clause.
However, @f[case] differs in the mechanism of clause selection.
The first thing @f[case] does is to evaluate the form @i[keyform]
to produce an object called the @i[key object].
Then @f[case] considers
each of the clauses in turn. If @i[key] is in the @i[keylist]
(that is, is @f[eql] to any item in the @i[keylist]) of a clause,
the consequents of that
clause are evaluated as an implicit @f[progn];
@f[case] returns what was returned by the last
consequent (or @false if there are no consequents in that clause).
If no clause is satisfied, @f[case] returns @false.
The keys in the keylists are @i[not] evaluated; literal key values
must appear in the keylists.
It is an error for the same key to appear in more than one clause;
a consequence is that the order of the clauses does not affect
the behavior of the @f[case] construct.
Instead of a @i[keylist], one may write one of the symbols
@true and @f[otherwise]. A clause with such a symbol
always succeeds and must be the last clause (this is an exception
to the order-independence of clauses).
See also @Macref[ecase] and @Macref[ccase], each of which provides
an implicit @f[otherwise] clause to signal an error if no clause
is satisfied.
If there is only one key for a clause, then that key may be written
in place of a list of that key, provided that no ambiguity results.
Such a ``singleton key'' may not be @nil (which is confusable
with @empty, a list of no keys), @true, @f[otherwise], or a cons.
@Incompatibility{The @lmlisp @f[caseq] construct
uses @f[eq] for the comparison.
In @lmlisp @f[case] therefore works for
fixnums but not bignums.
The @maclisp @f[caseq] construct simply prohibits the use of bignums;
indeed, it permits only fixnums and symbols as clause keys.
In the interest of hiding the fixnum-bignum distinction,
and for general language consistency,
@f[case] uses @f[eql] in @clisp.
The @interlisp @f[selectq] construct is similar to @f[case].⎇
@Enddefmac
@Defmac[Fun {typecase⎇, Args {@i[keyform] @Mstar<(@i[type] @mstar'@i[form]')>⎇]
@f[typecase] is a conditional that chooses one of its clauses by
examining the type of an object.
Its form is as follows:
@Lisp
(typecase @i[keyform]
(@i[type-1] @i[consequent-1-1] @i[consequent-1-2] ...)
(@i[type-2] @i[consequent-2-1] ...)
(@i[type-3] @i[consequent-3-1] ...)
...)
@Endlisp
Structurally @f[typecase] is much like @Macref[cond] or @Macref[case],
and it behaves like them
in selecting one clause and then executing all consequents of that clause.
It differs in the mechanism of clause selection.
The first thing @f[typecase] does is to evaluate the form @i[keyform]
to produce an object called the key object.
Then @f[typecase] considers
each of the clauses in turn. The @i[type] that appears
in each clause is a type specifier; it is not evaluated,
but is a literal type specifier.
The first clause for which the key
is of that clause's specified @i[type]
is selected, the consequents of this
clause are evaluated as an implicit @f[progn],
and @f[typecase] returns what was returned by the last
consequent (or @false if there are no consequents in that clause).
If no clause is satisfied, @f[typecase] returns @false.
As for @Macref[case], the symbol @true or @f[otherwise] may be written
for @i[type] to indicate that the clause should always be selected.
See also @Macref[etypecase] and @Macref[ctypecase], each of which provides
an implicit @f[otherwise] clause to signal an error if no clause
is satisfied.
It is permissible for more than one clause to specify a given type,
particularly if one is a subtype of another; the earliest applicable
clause is chosen. Thus for @f[typecase], unlike @Macref[case], the order
of the clauses may affect the behavior of the construct.
For example:
@lisp
@Tabset[35]
(typecase an-object
(string ...)@\;@r[This clause handles strings.]
((array t) ...)@\;@r[This clause handles general arrays.]
((array bit) ...)@\;@r[This clause handles bit arrays.]
(array ...)@\;@r[This handles all other arrays.]
((or list number) ...)@\;@r[This handles lists and numbers.]
(t ...))@\;@r[This handles all other objects.]
@Endlisp
A @clisp compiler may choose to issue a warning if
a clause cannot be selected because it is completely shadowed by
earlier clauses.
@Enddefmac
@Section[Blocks and Exits]
@label[BLOCK-RETURN-SECTION]
The @f[block] and @f[return-from] constructs provide a structured lexical
non-local exit facility. At any point lexically within a @f[block]
construct, a @f[return-from] with the same name may be used to
perform an immediate transfer of control that
exits from the @f[block]. In the most common cases this mechanism is
more efficient than the dynamic non-local exit facility
provided by @f[catch] and @f[throw], described in section
@ref[CATCH-THROW-SECTION].
@Defspec[Fun {block⎇, Args {@i[name] @Mstar<@i[form]>⎇]
The @f[block] construct executes each @i[form] from left to right,
returning whatever is returned by the last @i[form].
If, however, a @f[return] or @f[return-from] form that specifies the
same @i[name] is executed
during the execution of some @i[form], then the results
specified by the @f[return] or @f[return-from] are immediately
returned as the value of the @f[block] construct, and execution
proceeds as if the @f[block] had terminated normally.
In this, @f[block] differs from @Specref[progn]; the @f[progn] construct
has nothing to do with @f[return].
The @i[name] is not evaluated; it must be a symbol.
The scope of the @i[name] is lexical; only a @f[return] or @f[return-from]
textually contained in some @i[form] can exit from the block.
The extent of the name is dynamic.
Therefore it is only possible to exit from a given run-time incarnation of a
block once, either normally or by explicit return.
The @Macref[defun] form implicitly puts a @f[block] around the
body of the function defined; the @f[block] has the same name as the function.
Therefore one may use @f[return-from] to return
prematurely from a function defined by @f[defun].
The lexical scoping of the block name
is fully general and has consequences that may be surprising
to users and implementors of other @xlisp systems.
For example, the @f[return-from] in the following example actually does
``work'' in @clisp as one might expect:
@lisp
(block loser
(catch 'stuff
(mapcar #'(lambda (x) (if (numberp x)
(hairyfun x)
(return-from loser @nil)))
items)))
@endlisp
Depending on the situation, a @f[return] in @clisp
may not be simple.
A @f[return] can break up catchers if necessary to get
to the block in question.
It is possible for a ``closure'' created by @f[function] for
a lambda-expression to refer to a block name as long as the name
is lexically apparent.
@Enddefspec
@Defspec[Fun {return-from⎇, Args {@i[name] @mopt<@i[result]>⎇]
@Defmac1[Fun {return⎇, Args {@mopt<@i[result]>⎇]
@f[return-from]
is used to return from a @f[block] or from such constructs
as @f[do] and @f[prog] that implicitly establish a @f[block].
The @i[name] is not evaluated and must be a symbol.
A @f[block] construct with the same name must lexically
enclose the occurrence of @f[return-from];
whatever the evaluation of @i[result] produces
is immediately returned from the block.
(If the @i[result] form is omitted, it defaults to @nil.
As a matter of style, this form ought to be used to indicate that
the particular value returned doesn't matter.)
The @f[return-from] form itself never returns and cannot have a value;
it causes results to be returned from a @f[block] construct.
If the evaluation of @i[result] produces multiple values,
those multiple values are returned by the construct exited.
@f[(return @i[form])] is identical in meaning
to @f[(return-from @nil @i[form])]; it returns from a block named @nil.
Blocks established implicitly by iteration constructs such
as @f[do] are named @nil, so that @f[return] will exit properly from
such a construct.
@Enddefspec
@Section[Iteration]
@Index[iteration]
@clisp provides a number of iteration constructs. The @Macref[loop]
construct provides a trivial iteration facility; it is little more
than a @Specref[progn] with a branch from the bottom back to the top.
The @Macref[do]
and @Macref[do*] constructs provide a general iteration facility
for controlling the variation of several variables on each cycle.
For specialized iterations
over the elements of a list or @i[n] consecutive integers, @Macref[dolist] and
@Macref[dotimes] are provided. The @Specref[tagbody] construct is the most
general, permitting arbitrary @Specref[go] statements within it. (The
traditional @Macref[prog] construct is a synthesis of @f[tagbody],
@Specref[block], and @Specref[let].)
Most of the iteration constructs permit statically defined non-local exits in
the form of the @Specref[return-from] and @f[return] statements.
@subsection[Indefinite Iteration]
The @f[loop] construct is the simplest iteration facility.
It controls no variables, and simply executes its body repeatedly.
@Defmac[Fun {loop⎇, Args {@Mstar<@i[form]>⎇]
Each @i[form] is evaluated in turn from left to right.
When the last @i[form] has been evaluated, then the first @i[form]
is evaluated again, and so on, in a never-ending cycle.
The @f[loop] construct never returns a value. Its execution must be terminated
explicitly, using @Macref[return] or @Specref[throw], for example.
@f[loop], like most iteration constructs,
establishes an implicit block named @nil.
Thus @f[return] may be used to exit from a @f[loop] with specified results.
A @f[loop] construct has this meaning only if every @i[form] is
non-atomic (a list). The case where some @i[form] (possibly more than one) is
atomic is reserved for future extensions.
@Implementation{There have been several proposals for a powerful iteration
mechanism to be called @f[loop]. One version is provided in @lmlisp.
Implementors are encouraged to experiment with extensions to the @f[loop]
syntax, but users should be advised that in all likelihood some specific
set of extensions to @f[loop] will be adopted in a future revision of @clisp.⎇
@Enddefun
@Subsection[General Iteration]
In contrast to @f[loop], @f[do] and @f[do*] provide a powerful
and general mechanism for repetitively recalculating many variables.
@Defmac[Fun {do⎇, Args{(@Mstar<(@i[var] @mopt'@i[init] @mopt(@i[step])')>) (@i[end-test] @mstar<@i[result]>) @Mstar<@i[declaration]> @Mstar<@i[tag] @mor @i[statement]>⎇]
@Defmac1[Fun {do*⎇, Args{(@Mstar<(@i[var] @mopt'@i[init] @mopt(@i[step])')>) (@i[end-test] @mstar<@i[form]>) @Mstar<@i[declaration]> @Mstar<@i[tag] @mor @i[statement]>⎇]
The @f[do] special form provides a generalized iteration facility,
with an arbitrary number of ``index variables.''
These variables are bound within the iteration and stepped in parallel
in specified ways. They may be used both to generate successive
values of interest (such as successive integers) or to accumulate results.
When an end condition is met, the iteration terminates with a specified value.
In general, a @f[do] loop looks like this:
@Lisp
(do ((@i[var1] @i[init1] @i[step1])
(@i[var2] @i[init2] @i[step2])
...
(@i[varn] @i[initn] @i[stepn]))
(@i[end-test] . @i[result])
@Mstar<@i[declaration]>
. @i[tagbody])
@Endlisp
A @f[do*] loop looks exactly the same except that the name @f[do] is
replaced by @f[do*].
The first item in the form is a list of zero or more index-variable
specifiers. Each index-variable specifier is a list of the name of a
variable @i[var], an initial value @i[init],
and a stepping form @i[step].
If @i[init] is omitted, it defaults to @false.
If @i[step] is omitted, the @i[var] is not changed by the @f[do] construct
between repetitions (though code within the @f[do] is free to alter
the value of the variable by using @Specref[setq]).
An index-variable specifier can also be just the name of a variable.
In this case, the variable has an initial value of @false and is
not changed between repetitions.
As a matter
of style, it is recommended that an unadorned variable name
be written only when that
variable will be stored into (such as by @Specref[setq]) before its first
use. If it is important that the initial value is @false rather than
some undefined value, then it is clearer to write out
@f[(@i[varj] @false)] if the initial value is intended to mean ``false'' or
@f[(@i[varj] '@empty)] if the initial value is intended to be an empty
list.
Before the first iteration, all the @i[init] forms are evaluated, and
each @i[var] is bound to the value of its respective @i[init].
This is a binding, not an assignment; when the loop terminates,
the old values of those variables will be restored.
For @f[do], @i[all] of the @i[init] forms are evaluated @i[before] any @i[var]
is bound; hence all the
@i[init] forms may refer to the old bindings of all the variables
(that is, to the values visible before beginning execution of
the @f[do] construct).
For @f[do*], the first @f[init] form is evaluated, then the first
@f[var] is bound to that value, then the second @i[init] form
is evaluated, then the second @i[var] is bound, and so on;
in general, the @i[initj] form can refer to the @i[new] binding @i[vark]
if @i[k] < @i[j], and otherwise to the @i[old] binding of @i[vark].
The second element of the loop is a list of an end-testing
predicate form @i[end-test] and zero or more @i[result] forms.
This resembles a @f[cond] clause.
At the beginning of each iteration, after processing the variables,
the @i[end-test] is evaluated. If the result is
@false, execution proceeds with the body of the @f[do] (or @f[do*]) form.
If the
result is not @false, the @i[result] forms are evaluated in order
as an implicit @Specref[progn],
@Index{implicit @f[progn]⎇
and then @f[do] returns. @f[do] returns the results of evaluating
the last @i[result] form.
If there are no @i[result] forms, the value of @f[do] is @false.
Note that this is not quite analogous to the treatment of
clauses in a @Macref[cond] form, because a @f[cond] clause
with no result forms returns the (non-@nil) result of the test.
At the beginning of each iteration other than the first, the
index variables are updated as follows. All the @i[step] forms
are evaluated, from left to right, and the resulting values are
assigned to the respective index variables.
Any variable that has no associated @i[step] form is not assigned to.
For @i[do], all the @i[step] forms are evaluated before any variable
is updated; the assignment of values to variables is done in parallel,
as if by @Macref[psetq].
Because @i[all] of the @i[step] forms are evaluated before @i[any]
of the variables are altered, a step form when evaluated always has
access to the @i[old] values of @i[all] the index variables, even if other step
forms precede it.
For @f[do*], the first @f[step] form is evaluated, then the
value is assigned to the first @f[var], then the second @i[step] form
is evaluated, then the value is assigned to the second @i[var], and so on;
the assignment of values to variables is done sequentially,
as if by @Specref[setq].
For either @f[do] or @f[do*],
after the variables have been updated,
the end-test is evaluated as described above, and the iteration continues.
If the end-test of a @f[do] form is @f[@false],
the test will never succeed.
Therefore this provides an idiom for ``do forever'':
the @i[body] of the @f[do] is executed repeatedly, stepping variables
as usual. (The @Macref[loop] construct performs
a ``do forever'' that steps no variables.)
The infinite loop can be terminated by the use of @Macref[return],
@Specref[return-from], @Specref[go] to an outer level, or @Specref[throw].
For example:
@lisp
(do ((j 0 (+ j 1)))
(@false) ;@r[Do forever.]
(format t "@tilde@;%Input @tilde@;D:" j)
(let ((item (read)))
(if (null item) (return) ;@r[Process items until @false seen.]
(format t "@tilde@;&Output @tilde@;D: @tilde@;S" j (process item)))))
@Endlisp
The remainder of the @f[do] form constitutes an implicit @Specref[tagbody].
Tags may appear within the body of a @f[do] loop
for use by @Specref[go] statements appearing in the body (but such @f[go]
statements may not appear in the variable specifiers, the @i[end-test],
or the @i[result] forms).
When the end of a @f[do] body is reached, the next iteration cycle
(beginning with the evaluation of @i[step] forms) occurs.
An implicit @Specref[block] named @nil surrounds the entire @f[do] form.
A @Macref[return] statement may be used at any point to exit the loop
immediately.
@Specref[declare] forms may appear at the beginning of a @f[do] body.
They apply to code in the @f[do] body, to the bindings of the @f[do]
variables, to the @i[init] forms, to the @i[step] forms,
to the @i[end-test], and to the @i[result] forms.
@Incompatibility{``Old-style'' @maclisp @f[do] loops, that is, those
of the form @f[(do @i[var] @i[init] @i[step] @i[end-test] . @i[body])],
are not supported in @clisp.
Such old-style loops are considered obsolete,
and in any case are easily converted to a new-style
@f[do] with the insertion of three pairs of parentheses.
In practice the compiler can catch nearly all instances of old-style
@f[do] loops because they will not have a legal format anyway.⎇
Here are some examples of the use of @f[do]:
@Lisp
(do ((i 0 (+ i 1)) ;@r[Sets every null element of @f[a-vector] to zero.]
(n (array-dimension a-vector 0)))
((= i n))
(when (null (aref a-vector i))
(setf (aref a-vector i) 0)))
@Endlisp
The construction
@Lisp
(do ((x e (cdr x))
(oldx x x))
((null x))
@i[body])
@Endlisp
exploits parallel assignment to index variables. On the first
iteration, the value of @f[oldx] is whatever value @f[x] had before
the @f[do] was entered. On succeeding iterations, @f[oldx] contains
the value that @f[x] had on the previous iteration.
Very often an iterative algorithm can be most clearly expressed entirely
in the @i[step] forms of a @f[do], and the @i[body] is empty.
For example,
@Lisp
(do ((x foo (cdr x))
(y bar (cdr y))
(z '@empty (cons (f (car x) (car y)) z)))
((or (null x) (null y))
(nreverse z)))
@Endlisp
does the same thing as @f[(mapcar #'f foo bar)]. Note that the @i[step]
computation for @f[z] exploits the fact that variables are stepped in parallel.
Also, the body of the loop is empty. Finally, the use of @Funref[nreverse]
to put an accumulated @f[do] loop result into the correct order
is a standard idiom. Another example:
@Lisp
(defun list-reverse (list)
(do ((x list (cdr x))
(y '@empty (cons (car x) y)))
((endp x) y)))
@Endlisp
Note the use of @funref[endp] rather than @Funref[null] or @Funref[atom]
to test for the end of a list; this may result in more robust code.
As an example of nested loops, suppose that @f[env] holds a list
of conses. The @i[car] of each cons is a list of symbols,
and the @i[cdr] of each cons is a list of equal length containing
corresponding values. Such a data structure is similar to an association
list,
@Index[association list]
but is divided into ``frames''; the overall structure resembles a rib-cage.
A lookup function on such a data structure might be:
@Lisp
(defun ribcage-lookup (sym ribcage)
(do ((r ribcage (cdr r)))
((null r) @false)
(do ((s (caar r) (cdr s))
(v (cdar r) (cdr v)))
((null s))
(when (eq (car s) sym)
(return-from ribcage-lookup (car v))))))
@Endlisp
(Notice the use of indentation in the above example
to set off the bodies of the @f[do] loops.)
A @f[do] loop may be explained in terms of the more primitive constructs
@Specref[block], @Macref[return], @Specref[let], @Macref[loop], @Specref[tagbody],
and @Macref[psetq] as follows:
@lisp
(block nil
(let ((@i[var1] @i[init1])
(@i[var2] @i[init2])
...
(@i[varn] @i[initn]))
@Mstar<@i[declaration]>
(loop (when @i[end-test] (return (progn . @i[result])))
(tagbody . @i[tagbody])
(psetq @i[var1] @i[step1]
@i[var2] @i[step2]
...
@i[varn] @i[stepn]))))
@endlisp
@f[do*] is exactly like @f[do] except that the bindings and steppings
of the variables are performed sequentially rather than in parallel.
It is as if, in the above explanation,
@f[let] were replaced by @f[let*] and @f[psetq] were replaced
by @f[setq].
@Enddefmac
@Subsection[Simple Iteration Constructs]
The constructs @f[dolist] and @f[dotimes] execute a body of code
once for each value taken by a single variable. They are expressible
in terms of @f[do], but capture very common patterns of use.
Both @f[dolist] and @f[dotimes] perform
a body of statements repeatedly. On each iteration a specified
variable is bound to an element of interest that the body may
examine. @f[dolist] examines successive elements of a list,
and @f[dotimes] examines integers from 0 to @i[n]@minussign@;1
for some specified positive integer @i[n].
The value of any of these constructs may be specified by an optional result
form, which if omitted defaults to the value @false.
The @Macref[return] statement may be used to return
immediately from a @f[dolist] or @f[dotimes] form,
discarding any following iterations
that might have been performed; in effect, a @f[block] named @nil
surrounds the construct.
The body of the loop is implicitly a @Specref[tagbody] construct;
it may contain tags to serve as the targets of @Specref[go] statements.
Declarations may appear before the body of the loop.
@Defmac[Fun {dolist⎇, Args {(@i[var] @i[listform] @mopt<@i[resultform]>) @Mstar<@i[declaration]> @mstar<@i[tag] @mor @i[statement]>⎇]
@f[dolist] provides straightforward iteration over the elements of a list.
First @f[dolist]
evaluates the form @i[listform],
which should produce a list. It then executes the body
once for each element in the list, in order, with
the variable @i[var] bound to the element.
Then @i[resultform] (a single form, @i[not] an implicit @f[progn])
is evaluated, and the result is the value of the @f[dolist]
form. (When the @i[resultform] is evaluated, the control variable @i[var]
is still bound, and has the value @nil.)
If @i[resultform] is omitted, the result is @false.
@Lisp
(dolist (x '(a b c d)) (prin1 x) (princ " ")) @EV @false
@r[after printing ``@f[a b c d ]'']
@Endlisp
An explicit @f[return] statement may be used to terminate the loop
and return a specified value.
@Enddefmac
@Defmac[Fun {dotimes⎇, Args {(@i[var] @i[countform] @mopt<@i[resultform]>) @Mstar<@i[declaration]> @mstar<@i[tag] @mor @i[statement]>⎇]
@f[dotimes] provides straightforward iteration over a sequence of integers.
The expression
@f[(dotimes (@i[var] @i[countform] @i[resultform]) . @i[progbody])]
evaluates the form @i[countform], which should produce an integer. It then
performs @i[progbody] once for each integer from zero (inclusive) to
@i[count] (exclusive), in order, with the variable @i[var] bound to the
integer; if the value of @i[countform] is zero or negative,
then the @i[progbody] is
performed zero times. Finally, @i[resultform] (a single form, @i[not] an
implicit @f[progn]) is evaluated, and the result is the value of the
@f[dotimes] form. (When the @i[resultform] is evaluated, the control
variable @i[var] is still bound, and has as its value the number of times
the body was executed.)
If @i[resultform] is omitted, the result is @false.
An explicit @f[return] statement may be used to terminate the loop
and return a specified value.
Here is an example of the use of @f[dotimes] in processing strings:
@Lisp
;;; True if the specified subsequence of the string is a
;;; palindrome (reads the same forwards and backwards).
(defun palindromep (string @optional
(start 0)
(end (length string)))
(dotimes (k (floor (- end start) 2) @true)
(unless (char-equal (char string (+ start k))
(char string (- end k 1)))
(return @false))))
(palindromep "Able was I ere I saw Elba") @EV @true
(palindromep "A man, a plan, a canal--Panama!") @EV @false
(remove-if-not #'alpha-char-p ;Remove punctuation.
"A man, a plan, a canal--Panama!")
@EV "AmanaplanacanalPanama"
(palindromep
(remove-if-not #'alpha-char-p
"A man, a plan, a canal--Panama!")) @EV @true
(palindromep
(remove-if-not
#'alpha-char-p
"Unremarkable was I ere I saw Elba Kramer, nu?")) @EV @true
(palindromep
(remove-if-not
#'alpha-char-p
"A man, a plan, a cat, a ham, a yak,
a yam, a hat, a canal--Panama!")) @EV @true
@Endlisp
Altering the value of @i[var] in the body of the loop (by using @Specref[setq],
for example) will have unpredictable, possibly implementation-dependent
results. A @clisp compiler may choose to issue a warning if such a variable
appears in a @f[setq].
@Incompatibility{The @f[dotimes] construct is the closest thing
in @clisp to the @interlisp @f[rptq] construct.⎇
@Enddefmac
See also @Macref[do-symbols], @Macref[do-external-symbols],
and @Macref[do-all-symbols].
@Subsection[Mapping]
@Index[mapping]
Mapping is a type of iteration in which a function is
successively applied to pieces of one or more sequences.
The result of the iteration is a sequence containing the respective
results of the function applications.
There are several options for the way in which the pieces of the list are
chosen and for what is done with the results returned by the applications of
the function.
The function @Funref[map] may be used to map over any kind of sequence.
The following functions operate only on lists.
@Defun[Fun {mapcar⎇, Args {@i[function] @i[list] @rest @i[more-lists]⎇]
@Defun1[Fun {maplist⎇, Args {@i[function] @i[list] @rest @i[more-lists]⎇]
@Defun1[Fun {mapc⎇, Args {@i[function] @i[list] @rest @i[more-lists]⎇]
@Defun1[Fun {mapl⎇, Args {@i[function] @i[list] @rest @i[more-lists]⎇]
@Defun1[Fun {mapcan⎇, Args {@i[function] @i[list] @rest @i[more-lists]⎇]
@Defun1[Fun {mapcon⎇, Args {@i[function] @i[list] @rest @i[more-lists]⎇]
For each these mapping functions,
the first argument is a function and the rest must be lists.
The function must take as many arguments as there are lists.
@f[mapcar] operates on successive elements of the lists.
First the function is applied to the @i[car] of each list,
then to the @i[cadr] of each list, and so on.
(Ideally all the lists are the same length; if not,
the iteration terminates when the shortest list runs out,
and excess elements in other lists are ignored.)
The value returned by @f[mapcar] is a list of the
results of the successive calls to the function.
For example:
@lisp
(mapcar #'abs '(3 -4 2 -5 -6)) @EV (3 4 2 5 6)
(mapcar #'cons '(a b c) '(1 2 3)) @EV ((a . 1) (b . 2) (c . 3))
@Endlisp
@f[maplist] is like @f[mapcar] except that the function is applied to
the list and successive cdr's of that list rather than to successive
elements of the list.
For example:
@lisp
(maplist #'(lambda (x) (cons 'foo x))
'(a b c d))
@EV ((foo a b c d) (foo b c d) (foo c d) (foo d))
(maplist #'(lambda (x) (if (member (car x) (cdr x)) 0 1)))
'(a b a c d b c))
@EV (0 0 1 0 1 1 1)
;@r[An entry is @f[1] if the corresponding element of the input]
; @r[list was the last instance of that element in the input list.]
@Endlisp
@f[mapl] and @f[mapc] are like @f[maplist] and @f[mapcar]
respectively, except that they do not accumulate the results
of calling the function.
@Incompatibility{In all @xlisp systems since @lisp15,
@f[mapl] has been called @f[map]. In the chapter on sequences
it is explained why this was a bad choice. Here the name @f[map]
is used for the far more useful generic sequence mapper,
in closer accordance to the computer science literature,
especially the growing body of papers on functional programming.⎇
These functions are used when the function is being called merely for its
side effects, rather than its returned values.
The value returned by @f[mapl] or @f[mapc] is the second argument,
that is, the first sequence argument.
@f[mapcan] and @f[mapcon] are like @f[mapcar] and @f[maplist] respectively,
except that they combine the results of
the function using @Funref[nconc] instead of @f[list]. That is,
@Lisp
(mapcon @i[f] @i[x1] ... @i[xn])
@EQ (apply #'nconc (maplist @i[f] @i[x1] ... @i[xn]))
@Endlisp
and similarly for the relationship between @f[mapcan] and @f[mapcar].
Conceptually, these functions allow the mapped function to return
a variable number of items to be put into the output list.
This is particularly useful for effectively returning zero or one item:
@Lisp
(mapcan #'(lambda (x) (and (numberp x) (list x)))
'(a 1 b c 3 4 d 5))
@EV (1 3 4 5)
@Endlisp
In this case the function serves as a filter; this is a standard @xlisp
idiom using @f[mapcan].
(The function @Funref[remove-if-not] might have been useful in this
particular context, however.)
Remember that @f[nconc] is a destructive operation, and therefore
so are @f[mapcan] and @f[mapcon]; the lists returned by the @i[function]
are altered in order to concatenate them.
Sometimes a @f[do] or a straightforward recursion is preferable to a
mapping operation; however, the mapping functions should be used wherever they
naturally apply because this increases the clarity of the code.
The functional argument to a mapping function must be acceptable
to @f[apply]; it cannot be a macro or the name of a special form.
Of course, there is nothing wrong with using a function that has @optional
and @rest parameters as the functional argument.
@Enddefun
@Subsection[The ``Program Feature'']
@xlisp implementations since @xlisp 1.5 have had what was originally
called ``the program feature,'' as if it were impossible to write
programs without it! The @f[prog] construct allows one to
write in an @algol-like or @fortran-like statement-oriented
style, using @f[go] statements which can refer to tags in the
body of the @f[prog]. Modern @xlisp programming style tends to use
@f[prog] rather infrequently. The various iteration constructs,
such as @Macref[do], have bodies with the characteristics of a @f[prog].
(However, the ability to use @f[go] statements within iterations
constructs is very seldom used in practice.)
Three distinct operations are performed by @f[prog]: it binds local variables,
it permits use of the @f[return] statement, and it permits use of the @f[go]
statement.
In @clisp, these three operations have been separated into three
distinct constructs: @Specref[let], @Specref[block], and @Specref[tagbody].
These three constructs may be used independently as building blocks
for other types of constructs.
@Defspec[Fun {tagbody⎇, Args {@Mstar<@i[tag] @mor @i[statement]>⎇]
The part of a @f[prog] after the variable list is called the @i[body].
An item in the body may be a symbol or an integer, in which case it is called a
@i[tag], or an item in the body may be a list, in which case it is called a
@i[statement].
Each element of the body is processed from left to right.
A @i[tag] is ignored; a @i[statement]
is evaluated, and its results are discarded. If the end of the body
is reached, the @f[tagbody] returns @false.
If @f[(go @i[tag])] is evaluated, control jumps to the part of the body
labelled with the @i[tag].
@Incompatibility{The ``computed @f[go]'' feature of @maclisp is not
supported. The syntax of a computed @f[go] is idiosyncratic,
and the feature is not supported by @lmlisp, @newlisp, or @interlisp.
The computed @f[go] has been infrequently used an @maclisp anyway,
and is easily simulated with no loss of
efficiency by using a @f[case] statement each of whose
clauses performs a (non-computed) @f[go].⎇
The scope of the tags established by a @f[tagbody] is lexical,
and the extent is dynamic. Once a @f[tagbody] construct has
been exited, it is no longer legal to @f[go] to a @i[tag] in its body.
It is permissible for a @f[go] to jump to a @f[tagbody] that is not
the innermost @f[tagbody] construct containing that @f[go];
the tags established by a @f[tagbody] will only shadow other tags
of like name.
The lexical scoping of the @f[go] targets named by tags is
fully general and has consequences that may be surprising
to users and implementors of other @xlisp systems.
For example, the @f[go] in the following example actually does
``work'' in @clisp as one might expect:
@lisp
(tagbody
(catch 'stuff
(mapcar #'(lambda (x) (if (numberp x)
(hairyfun x)
(go lose)))
items))
(return)
lose
(error "I lost big!"))
@endlisp
Depending on the situation, a @f[go] in @clisp does not necessarily
correspond to a simple machine ``jump'' instruction!
A @f[go] can break up catchers if necessary to get
to the target. It is possible for a ``closure'' created by @f[function] for
a lambda-expression to refer to a @f[go] target as long as the tag
is lexically apparent. See chapter @ref[SCOPE] for an elaborate
example of this.
@Enddefspec
@Defmac[Fun {prog⎇, Args = {(@mstar<@i[var] @mor (@i[var] @Mopt'@i[init]')>) @Mstar<@i[declaration]> @mstar<@i[tag] @mor @i[statement]>⎇]
@Defmac1[Fun {prog*⎇, Args = {(@mstar<@i[var] @mor (@i[var] @Mopt'@i[init]')>) @Mstar<@i[declaration]> @mstar<@i[tag] @mor @i[statement]>⎇]
The @f[prog] construct is a synthesis of @f[let], @f[block],
and @f[tagbody], allowing bound variables and the use of @f[return] and @f[go]
within a single construct. A typical @f[prog] construct looks like this:
@Lisp
(prog (@i[var1] @i[var2] (@i[var3] @i[init3]) @i[var4] (@i[var5] @i[init5]))
@Mstar<@i[declaration]>
@i[statement1]
@i[tag1]
@i[statement2]
@i[statement3]
@i[statement4]
@i[tag2]
@i[statement5]
...
)
@Endlisp
The list after the keyword @f[prog] is a set of specifications for binding
@i[var1], @i[var2], etc.,
which are temporary variables bound locally to the @f[prog].
This list is processed exactly as the list in a @Specref[let] statement:
first all the @i[init] forms are evaluated from left to right
(where @false is used for
any omitted @i[init] form), and then the variables are all bound in
parallel to the respective results.
Any @i[declaration] appearing in the @f[prog] is used as if appearing
at the top of the @f[let] body.
The body of the @f[prog] is executed as if it were a @Specref[tagbody]
construct; the @Specref[go] statement may be used to transfer control
to a @i[tag].
A @f[prog] implicitly establishes a @Specref[block] named @nil around
the entire @f[prog] construct, so that @Macref[return] may be used
at any time to exit from the @f[prog] construct.
Here is a fine example of what can be done with @f[prog]:
@Lisp
(defun king-of-confusion (w)
"Take a cons of two lists and make a list of conses.
Think of this function as being like a zipper."
(prog (x y z) ;@r[Initialize @f[x], @f[y], @f[z] to @false]
(setq y (car w) z (cdr w))
loop
(cond ((null y) (return x))
((null z) (go err)))
rejoin
(setq x (cons (cons (car y) (car z)) x))
(setq y (cdr y) z (cdr z))
(go loop)
err
(cerror "Will self-pair extraneous items"
"Mismatch - gleep! }S" y)
(setq z y)
(go rejoin)))
@Endlisp
which is accomplished somewhat more perspicuously by:
@Lisp
(defun prince-of-clarity (w)
"Take a cons of two lists and make a list of conses.
Think of this function as being like a zipper."
(do ((y (car w) (cdr y))
(z (cdr w) (cdr z))
(x '@empty (cons (cons (car y) (car z)) x)))
((null y) x)
(when (null z)
(cerror "Will self-pair extraneous items"
"Mismatch - gleep! }S" y)
(setq z y))))
@Endlisp
The @f[prog] construct may be explained in terms of the simpler
constructs @Specref[block], @Specref[let], and @Specref[tagbody] as
follows:
@lisp
(prog @i[variable-list] @mstar<@i[declaration]> . @i[body])
@eq (block nil (let @i[variable-list] @mstar<@i[declaration]> (tagbody . @i[body])))
@endlisp
The @f[prog*] special form is almost the same as @f[prog]. The only
difference is that the binding and initialization of the temporary
variables is done @i[sequentially], so that the @i[init] form for each
one can use the values of previous ones.
Therefore @f[prog*] is to @f[prog] as @Specref[let*] is to @Specref[let].
For example,
@Lisp
(prog* ((y z) (x (car y)))
(return x))
@Endlisp
returns the car of the value of @f[z].
@Enddefmac
@Defspec[Fun {go⎇, Args {@i[tag]⎇]
The @f[(go @i[tag])] special form is used to do a ``go to'' within
a @Specref[tagbody] construct. The @i[tag] must be a symbol or an integer;
the @i[tag] is not evaluated.
@f[go] transfers control to the point in the body labelled by a
tag @f[eql] to the one given. If there is no such tag in the body, the
bodies of lexically containing @f[tagbody] constructs
(if any) are examined as well.
It is an error if there is no matching tag lexically visible
to the point of the @f[go].
The @f[go] form does not ever return a value.
As a matter of style, it is recommended that the user think twice before
using a @f[go]. Most purposes of @f[go] can be accomplished with one of
the iteration primitives, nested conditional forms, or
@Specref[return-from]. If the use of @f[go] seems to be unavoidable,
perhaps the control structure implemented by @f[go] should be packaged
as a macro definition.
@Enddefspec
@Section[Multiple Values]
@Index[multiple values]
Ordinarily the result of calling a @xlisp function is a single @xlisp object.
Sometimes, however, it is convenient for a function to compute several
objects and return them.
@clisp provides a mechanism for handling multiple values directly.
This mechanism is cleaner and more efficient than the usual tricks
involving returning a list of results or stashing results in global
variables.
@Subsection[Constructs for Handling Multiple Values]
Normally multiple values are not used. Special forms are
required both to @i[produce] multiple values and to @i[receive] them.
If the caller of a function does not request multiple values,
but the called function produces multiple values, then the first
value is given to the caller and all others are discarded;
if the called function produces zero values, then the caller gets @false
as a value.
The primary primitive for producing multiple values is @Funref[values],
which takes any number of arguments and returns that many values. If the
last form in the body of a function is a @f[values] with three arguments,
then a call to that function will return three values. Other special
forms also produce multiple values, but they can be described in terms of
@f[values]. Some built-in @clisp functions, such as @Funref[floor] return
multiple values; those that do are so documented.
The special forms for receiving multiple values are as follows:
@lisp
multiple-value-list
multiple-value-call
multiple-value-prog1
multiple-value-bind
multiple-value-setq
@endlisp
These specify a form to evaluate and an indication of where to put
the values returned by that form.
@Defun[Fun {values⎇, Args {@rest @i[args]⎇]
All of the arguments are returned, in order, as values.
For example:
@lisp
(defun polar (x y)
(values (sqrt (+ (* x x) (* y y))) (atan y x)))
(multiple-value-bind (r theta) (polar 3.0 4.0)
(vector r theta))
@EV #(5.0 0.9272952)
@Endlisp
The expression @f[(values)] returns zero values. This is the standard idiom
for returning no values from a function.
Sometimes it is desirable to indicate explicitly that a function will return
exactly one value. For example, the function
@lisp
(defun foo (x y)
(floor (+ x y) y))
@endlisp
will return two values because @Funref[floor] returns
two values. It may be that the second value makes no sense,
or that for efficiency reasons it is desired not to compute the
second value. The @f[values] function is the standard idiom
for indicating that only one value is to be returned:
@lisp
(defun foo (x y)
(values (floor (+ x y) y)))
@endlisp
This works because @f[values] returns exactly @i[one] value for each of
its argument forms; as for any function call,
if any argument form to @f[values] produces more than one value, all but the
first are discarded.
There is absolutely no way in @clisp for a caller to distinguish between
returning a single value in the ordinary manner and returning
exactly one ``multiple value.'' For example, the values returned
by the expressions @f[(+ 1 2)] and @f[(values (+ 1 2))] are identical
in every respect: the single value @f[3].
@Enddefun
@Defcon[Var {multiple-values-limit⎇]
The value of @f[multiple-values-limit] is a positive integer that is
the upper exclusive bound on the number of values that may
be returned from a function. This bound depends on the implementation,
but will not be smaller than 20.
(Implementors are encouraged to make this limit as large as practicable
without sacrificing performance.)
See @conref[lambda-parameters-limit] and @conref[call-arguments-limit].
@Enddefcon
@Defun[Fun {values-list⎇, Args {@i[list]⎇]
All of the elements of @i[list] are returned as multiple values.
For example:
@lisp
(values-list (list a b c)) @EQ (values a b c)
@Endlisp
In general,
@lisp
(values-list @i[list]) @EQ (apply #'values @i[list])
@endlisp
but @f[values-list] may be clearer or more efficient.
@Enddefun
@Defmac[Fun {multiple-value-list⎇, Args {@i[form]⎇]
@f[multiple-value-list] evaluates @i[form] and returns a list of
the multiple values it returned.
For example:
@lisp
(multiple-value-list (floor -3 4)) @EV (-1 1)
@Endlisp
@f[multiple-value-list] and @f[values-list] are therefore inverses
of each other.
@Enddefmac
@Defspec[Fun {multiple-value-call⎇, Args {@i[function] @mstar<@i[form]>⎇]
@f[multiple-value-call] first evaluates @i[function] to obtain a function
and then evaluates all of the @i[forms]. All the values
of the @i[forms] are gathered together (not just one value from each)
and given as arguments to the function. The result of @f[multiple-value-call]
is whatever is returned by the function.
For example:
@lisp
(+ (floor 5 3) (floor 19 4))
@EQ (+ 1 4) @EV 5
(multiple-value-call #'+ (floor 5 3) (floor 19 4))
@EQ (+ 1 2 4 3) @EV 10
(multiple-value-list @i[form]) @EQ (multiple-value-call #'list @i[form])
@Endlisp
@Enddefspec
@Defspec[Fun {multiple-value-prog1⎇, Args {@i[form] @mstar<@i[form]>⎇]
@f[multiple-value-prog1] evaluates the first @i[form] and saves all the values
produced by that form. It then evaluates the other @i[form]s
from left to right, discarding their values. The values produced
by the first @i[form] are returned by @f[multiple-value-prog1]. See @Macref[prog1],
which always returns a single value.
@Enddefspec
@Defmac[Fun {multiple-value-bind⎇, Args {(@mstar<@i[var]>) @i[values-form] @Mstar<@i[declaration]> @Mstar<@i[form]>⎇]
The @i[values-form] is evaluated, and each of the variables @i[var] is
bound to the respective value returned by that form. If there are more
variables than values returned, extra values of @false are given to the
remaining variables. If there are more values than variables, the excess
values are simply discarded. The variables are bound to the values over
the execution of the forms, which make up an implicit @f[progn].
@Incompatibility{This is compatible with @lmlisp.⎇
For example:
@lisp
(multiple-value-bind (x) (floor 5 3) (list x)) @EV (1)
(multiple-value-bind (x y) (floor 5 3) (list x y)) @EV (1 2)
(multiple-value-bind (x y z) (floor 5 3) (list x y z))
@EV (1 2 @false)
@Endlisp
@Enddefmac
@Defmac[Fun {multiple-value-setq⎇, Args {@i[variables] @i[form]⎇]
The @i[variables] must be a list of variables. The @i[form] is
evaluated, and the variables are @i[set] (not bound) to the values
returned by that form. If there are more variables than values returned,
extra values of @false are assigned to the remaining variables. If there
are more values than variables, the excess values are simply discarded.
@Incompatibility{In @lmlisp this is called @f[multiple-value].
The added clarity of the name @f[multiple-value-setq] in @clisp was deemed
worth the incompatibility with @lmlisp.⎇
@f[multiple-value-setq] always returns a single value, which is the first
value returned by @i[form], or @false if @i[form] produces zero values.
@Enddefmac
@Subsection[Rules Governing the Passing of Multiple Values]
It is often the case that the value
of a special form or macro call
is defined to be the value of one of its subforms.
For example, the
value of a @f[cond] is the value of the last form in the selected clause.
In most such cases, if the subform produces multiple values, then the original
form will also produce all of those values.
This @i[passing back] of
multiple values of course has no effect unless eventually one of the
special forms for receiving multiple values is reached.
To be explicit, multiple values can result from a special form
under precisely these circumstances:
@Begin[Description, Indent -.2 in, Leftmargin +.2in]
@Begin[Multiple]
@i[Evaluation and Application]@\
@Begin[Itemize]
@Funref[eval] returns multiple values if the form given it to
evaluate produces multiple values.
@Funref[apply], @Funref[funcall], and @Specref[multiple-value-call],
pass back multiple values from the function applied or called.
@End[Itemize]
@End[Multiple]
@Begin[Multiple]
@i[Implicit @f[progn] contexts]@\
@Begin[Itemize]
The special form @Specref[progn]
passes backs multiple values resulting from evaluation of the
last subform. Other situations referred to as ``implicit @f[progn],''
where several forms are evaluated and the results of all but the last form
are discarded, also pass back multiple values from the last form.
These situations include the body of a lambda-expression,
in particular those constructed by @Macref[defun],
@Macref[defmacro], and @Macref[deftype].
Also included are bodies of the constructs
@Specref[eval-when],
@Specref[progv], @Specref[let],
@Specref[let*], @Macref[when], @Macref[unless],
@Specref[block],
@Macref[multiple-value-bind], and @Specref[catch],
as well as clauses in such conditional
constructs as
@Macref[case], @Macref[typecase],
@Macref[ecase], @Macref[etypecase], @Macref[ccase], and @Macref[ctypecase].
@End[Itemize]
@End[Multiple]
@Begin[Multiple]
@i[Conditional constructs]@\
@Begin[Itemize]
@Specref[if] passes back multiple values from whichever subform is selected
(the @i[then] form or the @i[else] form).
@Macref[and] and @Macref[or] pass back multiple values from the last subform
but not from subforms other than the last.
@Macref[cond] passes back multiple values from the last subform of
the implicit @f[progn] of the selected clause.
If, however, the clause selected is a singleton clause,
then only a single value (the non-@false predicate value)
is returned. This is true even if the singleton clause is
the last clause of the @f[cond]. It is @i[not] permitted to
treat a final clause @f[(x)] as being the same as @f[(t x)]
for this reason; the latter passes back multiple values from the form @f[x].
@End[Itemize]
@End[Multiple]
@Begin[Multiple]
@i[Returning from a block]@\
@Begin[Itemize]
The @Specref[block] construct passes back multiple values from its last subform
when it exits normally. If @Specref[return-from] (or @f[return]) is
used to terminate the @f[block] prematurely, then @f[return-from]
passes back multiple values from its subform as the values of the
terminated @f[block]. Other constructs that create implicit blocks,
such as
@Macref[do], @Macref[dolist], @Macref[dotimes], @Macref[prog], and
@Macref[prog*], also pass back multiple values specified by
@f[return-from] (or @Macref[return]).
@f[do] passes back multiple values from
the last form of the exit clause, exactly as if the exit clause
were a @f[cond] clause. Similarly, @f[dolist] and @f[dotimes]
pass back multiple values from the @i[resultform] if that is executed.
These situations are all examples of implicit uses of @f[return-from].
@End[Itemize]
@End[Multiple]
@Begin[Multiple]
@i[Throwing out of a catch]@\
@Begin[Itemize]
The @Specref[catch] construct returns multiple values if
the result form in a @Specref[throw] exiting from
such a catch produces multiple values.
@End[Itemize]
@End[Multiple]
@Begin[Multiple]
@i[Miscellaneous situations]@\
@Begin[Itemize]
@Specref[multiple-value-prog1] passes back multiple values from its first
subform. However, @Macref[prog1] always returns a single value.
@Specref[unwind-protect] returns multiple values if the form it protects
returns mutliple values.
@Specref[the] returns multiple values if the form it contains returns
multiple values.
@End[Itemize]
@End[Multiple]
@End[Description]
Among special forms that @i[never] pass back multiple values are
@Specref[setq], @Macref[multiple-value-setq], @Macref[prog1], and
@Macref[prog2].
The conventional way to force only one value to be returned from a form @f[x]
is to write @f[(values x)].
The most important rule about multiple values is:
@b[No matter how many values a form produces,
if the form is an argument form in a function call,
then exactly @i[one] value (the first one) is used.]
For example, if you write @f[(cons (floor x))], then @f[cons] will always
receive @i[exactly] one argument (which is of course an error),
even though @f[floor] returns two values. To pass both values from @f[floor]
to @f[cons], one must write something like
@f[(multiple-value-call #'cons (floor x))].
In an ordinary function call,
each argument form produces exactly @i[one] argument; if such a form
returns zero values, @false is used for the argument, and if more than one
value, all but the first are discarded.
Similarly, conditional constructs such as @f[if] that test the value of a form
will use exactly one value, the first one, from that form and discard the rest;
such constructs will use @false as the test value if zero values are returned.
@Section[Dynamic Non-local Exits]
@label[CATCH-THROW-SECTION]
@Index[non-local exit]
@Index[dynamic exit]
@Index[catch]
@Index[throw]
@clisp provides a facility for exiting from a complex process
in a non-local, dynamically scoped manner. There are two classes of
special forms for this purpose, called @i[catch] forms and @i[throw]
forms, or simply @i[catches] and @i[throws]. A catch form evaluates some
subforms in such a way that, if a throw form is executed during such
evaluation, the evaluation is aborted at that point and the catch form
immediately returns a value specified by the throw. Unlike @Specref[block]
and @Macref[return] (section @ref[BLOCK-RETURN-SECTION]),
which allow for exiting a @f[block] form from any
point lexically within the body of the @f[block], the catch/throw
mechanism works even if the throw form is not textually within the body
of the catch form. The throw need only occur within the extent (time
span) of the evaluation of the body of the catch. This is analogous to
the distinction between dynamically bound (special) variables and
lexically bound (local) variables.
@Defspec[Fun {catch⎇, Args {@i[tag] @mstar<@i[form]>⎇]
The @f[catch] special form serves as a target for transfer
of control by @f[throw].
The form @i[tag] is evaluated first to produce an object
that names the catch; it may be any @xlisp object.
A catcher is then established with the object as the tag.
The @i[forms] are evaluated as an implicit @f[progn],
and the results of the last form are returned,
except that if during the evaluation of the @i[forms]
a throw should be executed such that the tag
of the throw matches (is @f[eq] to) the tag of the @f[catch]
and the catcher is the most recent outstanding catcher with that tag,
then the evaluation of the @i[forms] is aborted and the results
specified by the throw
are immediately returned from the @f[catch] expression.
The catcher established by the @f[catch] expression is disestablished
just before the results are returned.
The tag is used to match throws with catches.
@f[(catch 'foo @i[form])] will catch a @f[(throw 'foo @i[form])] but
not a @f[(throw 'bar @i[form])]. It is an error if @f[throw] is done
when there is no suitable @f[catch] ready to catch it.
Catch tags are compared using @f[eq],
not @f[eql]; therefore numbers and characters
should not be used as catch tags.
@Incompatibility{The name @f[catch] comes from @maclisp,
but the syntax of @f[catch] in @clisp is different.
The @maclisp syntax was @f[(catch @i[form] @i[tag])],
where the @i[tag] was not evaluated.⎇
@Enddefspec
@Index[unwind protection]
@Index[cleanup handler]
@Defspec[Fun {unwind-protect⎇, Args {@i[protected-form] @mstar<@i[cleanup-form]>⎇]
Sometimes it is necessary to evaluate a form and make sure that
certain side effects take place after the form is evaluated;
a typical example is:
@Lisp
(progn (start-motor)
(drill-hole)
(stop-motor))
@Endlisp
The non-local exit facility of @clisp creates a situation in which
the above code won't work, however: if @f[drill-hole] should
do a throw to a catch that is outside of the @f[progn]
form (perhaps because the drill bit broke),
then @f[(stop-motor)] will never be evaluated
(and the motor will presumably be left running).
This is particularly likely if @f[drill-hole] causes a @xlisp error
and the user tells the error-handler to give up and abort
the computation.
(A possibly more practical example might be:
@Lisp
(prog2 (open-a-file)
(process-file)
(close-the-file))
@Endlisp
where it is desired always to close the file when the computation
is terminated for whatever reason. This case is so important
that @clisp provides the special form @Macref[with-open-file] for
this purpose.)
In order to allow the example hole-drilling program to work, it can
be rewritten using @f[unwind-protect] as follows:
@Lisp
(unwind-protect
(progn (start-motor)
(drill-hole))
(stop-motor))
@Endlisp
If @f[drill-hole] does a throw that attempts to quit out of the
@f[unwind-protect], then @f[(stop-motor)] will be executed.
This example assumes that it is correct to call @f[stop-motor]
even if the motor has not yet been started. Remember that
an error or interrupt may cause an exit even before any initialization
forms have been executed. Any state restoration code
should operate correctly no matter where in the protected code an
exit occurred. For example, the following code
is not correct:
@lisp
(unwind-protect
(progn (incf *access-count*)
(perform-access))
(decf *access-count*))
@endlisp
If an exit occurs before completion of the @f[incf] operation
the @f[decf] operation will be executed anyway, resulting in an
incorrect value for @var[access-count].
The correct way to code this is as follows:
@lisp
(let ((old-count *access-count*))
(unwind-protect
(progn (incf *access-count*)
(perform-access))
(setq *access-count* old-count)))
@endlisp
As a general rule, @f[unwind-protect] guarantees to execute
the @i[cleanup-forms] before exiting, whether it terminates
normally or is aborted by a throw of some kind.
(If, however, an exit occurs during execution of the @i[cleanup-forms],
no special action is taken. The @i[cleanup-forms] of an @f[unwind-protect]
are not protected by that @f[unwind-protect], though they may be
protected if that @f[unwind-protect] occurs within the protected
form of another @f[unwind-protect].)
@f[unwind-protect] returns whatever results from evaluation of
the @i[protected-form] and discards all the results
from the @i[cleanup-forms].
It should be emphasized that @f[unwind-protect] protects against
@i[all] attempts to exit from the protected form,
including not only such ``dynamic exit'' facilities such as @Specref[throw]
but also such ``lexical exit'' facilities as @Specref[go] and
@Specref[return-from]. Consider this situation:
@lisp
(tagbody
(let ((x 3))
(unwind-protect
(if (numberp x) (go out))
(print x)))
out
...)
@endlisp
When the @f[go] is executed, the call to @f[print] is executed first,
and then the transfer of control to the tag @f[out] is completed.
@enddefspec
@Defspec[Fun {throw⎇, Args {@i[tag] @i[result]⎇]
The @f[throw] special form transfers control to a matching
@f[catch] construct.
The @i[tag] is evaluated first to produce an object
called the throw tag; then the @i[result] form is evaluated,
and its results are saved (if the @i[result] form produces
multiple values, then @i[all] the values are saved).
The most recent outstanding catch whose tag matches the throw tag
is exited; the saved results are returned as the value(s) of the catch.
A @f[catch] matches only if the catch tag is @f[eq] to the throw tag.
In the process, dynamic variable
bindings are undone back to the point of the catch, and any intervening
@f[unwind-protect] cleanup code is executed.
The @i[result] form is evaluated before the unwinding process commences,
and whatever results it produces are returned from the catch.
If there is no outstanding catcher whose tag matches the throw tag,
no unwinding of the stack is performed, and an error is signalled.
When the error is signalled, the outstanding catchers and the dynamic
variable bindings are those in force at the point of the throw.
@Implementation{These requirements imply that throwing should typically
make two passes over the control stack. In the first pass it simply
searches for a matching catch. In this search every @f[catch]
must be considered, but every
@f[unwind-protect] should be ignored. On the second pass the stack
is actually unwound, one frame at a time, undoing dynamic bindings
and outstanding @f[unwind-protect] constructs in reverse order of creation
until the matching catch is reached.⎇
@Incompatibility{The name @f[throw] comes from @maclisp,
but the syntax of @f[throw] in @clisp is different.
The @maclisp syntax was @f[(throw @i[form] @i[tag])],
where the @i[tag] was not evaluated.⎇
@Enddefspec